1 {-# LANGUAGE FlexibleContexts, PatternSignatures, DeriveDataTypeable #-}
11 import Language.Haskell.Parser (parseModule, ParseResult(..))
12 import Language.Haskell.Syntax
14 import Control.Monad.Error
15 import Control.Monad.Reader
17 import qualified Data.Map as M
20 import Data.Generics.Schemes
24 data TypVar = TypVar Int -- alpha, beta etc.
25 | TypInst Int Bool -- t1,t2 etc
26 deriving (Show, Eq, Typeable, Data)
28 instType :: Bool -> Typ -> Typ
29 instType rightSide typ = everywhere (mkT (\(TypVar i) -> TypInst i rightSide)) typ
31 data Typ = TVar TypVar
33 | All TypVar Typ --wir geben Typen ohne Quantifier an
40 deriving (Show, Eq, Typeable, Data)
42 unquantify :: Typ -> Typ
43 unquantify (All _ t) = unquantify t
44 unquantify (AllStar _ t) = unquantify t
47 parseType :: String -> Typ
48 parseType = either error id . parseType'
50 -- | A simple type parser.
52 -- > parseType "Int -> [Either a b] -> (a,b)" :: Either String Typ
54 -- Right (All (TypVar 3) (All (TypVar 4) (Arrow Int (Arrow (List (TEither (TVar (TypVar 3)) (TVar (TypVar 4)))) (TPair (TVar (TypVar 3)) (TVar (TypVar 4)))))))
56 parseType' :: (MonadError String t) => String -> t Typ
57 parseType' s = let (vars,types) = case span (/='.') s of
58 (v,'.':t) -> (words v, t)
60 in case parseModule ("x :: " ++ types) of
61 ParseOk hsModule -> do
62 hstype <- extractTheOneType hsModule
63 let varmap = createVarMap hstype
64 specials = mapMaybe (flip M.lookup varmap) (map HsIdent vars)
65 typ <- runReaderT (simplifiyType hstype) varmap
66 return (quantify specials typ)
68 throwError ("Parse error at (" ++ show (srcLine l) ++ ":" ++ show (srcColumn l) ++ ").")
70 extractTheOneType :: (MonadError String m) => HsModule -> m HsType
71 extractTheOneType (HsModule _ _ _ _ [HsTypeSig _ _ (HsQualType [] t)]) = return t
72 extractTheOneType _ = throwError "parseModule gave unexpected result"
74 createVarMap :: HsType -> M.Map HsName TypVar
75 createVarMap hstype = M.fromList $ zip
76 (nub (listify isVar hstype))
78 where isVar (HsIdent (x:_)) | isLower x = True
82 simplifiyType :: (MonadReader (M.Map HsName TypVar) m, MonadError String m) =>
84 simplifiyType (HsTyFun t1 t2)
85 = liftM2 Arrow (simplifiyType t1) (simplifiyType t2)
86 simplifiyType (HsTyTuple [t1,t2])
87 = liftM2 TPair (simplifiyType t1) (simplifiyType t2)
88 simplifiyType (HsTyTuple _) = throwError "Tuple with more than one type not supported."
89 simplifiyType (HsTyVar name) = do Just tv <- asks (M.lookup name)
91 simplifiyType (HsTyCon (UnQual (HsIdent "Int")))
93 simplifiyType (HsTyApp (HsTyApp (HsTyCon (UnQual (HsIdent "Either"))) t1) t2)
94 = liftM2 TEither (simplifiyType t1) (simplifiyType t2)
95 simplifiyType (HsTyApp (HsTyCon (Special HsListCon)) t)
96 = liftM List (simplifiyType t)
98 = throwError ("Unsupported type " ++ show t)
100 quantify :: [TypVar] -> Typ -> Typ
101 quantify special t = foldr allQuant t (nub (listify (\(_::TypVar) -> True) t))
102 where allQuant v | v `elem` special = All v
103 | otherwise = AllStar v