1 {-# LANGUAGE FlexibleContexts, PatternSignatures, DeriveDataTypeable #-}
10 import Language.Haskell.Parser (parseModule, ParseResult(..))
11 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 (All _ t) = unquantify t
43 unquantify (AllStar _ t) = unquantify t
46 parseType = either error id . parseType'
48 -- | A simple type parser.
50 -- > parseType "Int -> [Either a b] -> (a,b)" :: Either String Typ
52 -- 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)))))))
54 parseType' :: (MonadError String t) => String -> t Typ
55 parseType' s = let (vars,types) = case span (/='.') s of
56 (v,'.':t) -> (words v, t)
58 in case parseModule ("x :: " ++ types) of
59 ParseOk hsModule -> do
60 hstype <- extractTheOneType hsModule
61 let varmap = createVarMap hstype
62 specials = mapMaybe (flip M.lookup varmap) (map HsIdent vars)
63 typ <- runReaderT (simplifiyType hstype) varmap
64 return (quantify specials typ)
66 throwError ("Parse error at (" ++ show (srcLine l) ++ ":" ++ show (srcColumn l) ++ ").")
68 extractTheOneType :: (MonadError String m) => HsModule -> m HsType
69 extractTheOneType (HsModule _ _ _ _ [HsTypeSig _ _ (HsQualType [] t)]) = return t
70 extractTheOneType _ = throwError "parseModule gave unexpected result"
72 createVarMap :: HsType -> M.Map HsName TypVar
73 createVarMap hstype = M.fromList $ zip
74 (nub (listify isVar hstype))
76 where isVar (HsIdent (x:xs)) | isLower x = True
80 simplifiyType :: (MonadReader (M.Map HsName TypVar) m, MonadError String m) =>
82 simplifiyType (HsTyFun t1 t2)
83 = liftM2 Arrow (simplifiyType t1) (simplifiyType t2)
84 simplifiyType (HsTyTuple [t1,t2])
85 = liftM2 TPair (simplifiyType t1) (simplifiyType t2)
86 simplifiyType (HsTyTuple _) = throwError "Tuple with more than one type not supported."
87 simplifiyType (HsTyVar name) = do Just tv <- asks (M.lookup name)
89 simplifiyType (HsTyCon (UnQual (HsIdent "Int")))
91 simplifiyType (HsTyApp (HsTyApp (HsTyCon (UnQual (HsIdent "Either"))) t1) t2)
92 = liftM2 TEither (simplifiyType t1) (simplifiyType t2)
93 simplifiyType (HsTyApp (HsTyCon (Special HsListCon)) t)
94 = liftM List (simplifiyType t)
96 = throwError ("Unsupported type " ++ show t)
98 quantify :: [TypVar] -> Typ -> Typ
99 quantify special t = foldr all t (nub (listify (\(_::TypVar) -> True) t))
100 where all v | v `elem` special = All v
101 | otherwise = AllStar v