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
27 deriving (Show, Eq, Typeable, Data)
29 instType :: Bool -> Typ -> Typ
30 instType rightSide typ = everywhere (mkT (\(TypVar i) -> TypInst i rightSide)) typ
32 data Typ = TVar TypVar
34 | All TypVar Typ --wir geben Typen ohne Quantifier an
41 deriving (Show, Eq, Typeable, Data)
43 unquantify :: Typ -> Typ
44 unquantify (All _ t) = unquantify t
45 unquantify (AllStar _ t) = unquantify t
48 parseType :: String -> Typ
49 parseType = either error id . parseType'
51 -- | A simple type parser.
53 -- > parseType "Int -> [Either a b] -> (a,b)" :: Either String Typ
55 -- 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)))))))
57 parseType' :: (MonadError String t) => String -> t Typ
58 parseType' s = let (vars,types) = case span (/='.') s of
59 (v,'.':t) -> (words v, t)
61 in case parseModule ("x :: " ++ types) of
62 ParseOk hsModule -> do
63 hstype <- extractTheOneType hsModule
64 let varmap = createVarMap hstype
65 specials = mapMaybe (flip M.lookup varmap) (map HsIdent vars)
66 typ <- runReaderT (simplifiyType hstype) varmap
67 return (quantify specials typ)
69 throwError ("Parse error at (" ++ show (srcLine l) ++ ":" ++ show (srcColumn l) ++ ").")
71 extractTheOneType :: (MonadError String m) => HsModule -> m HsType
72 extractTheOneType (HsModule _ _ _ _ [HsTypeSig _ _ (HsQualType [] t)]) = return t
73 extractTheOneType _ = throwError "parseModule gave unexpected result"
75 createVarMap :: HsType -> M.Map HsName TypVar
76 createVarMap hstype = M.fromList $ zip
77 (nub (listify isVar hstype))
79 where isVar (HsIdent (x:_)) | isLower x = True
83 simplifiyType :: (MonadReader (M.Map HsName TypVar) m, MonadError String m) =>
85 simplifiyType (HsTyFun t1 t2)
86 = liftM2 Arrow (simplifiyType t1) (simplifiyType t2)
87 simplifiyType (HsTyTuple [t1,t2])
88 = liftM2 TPair (simplifiyType t1) (simplifiyType t2)
89 simplifiyType (HsTyTuple _) = throwError "Tuple with more than one type not supported."
90 simplifiyType (HsTyVar name) = do Just tv <- asks (M.lookup name)
92 simplifiyType (HsTyCon (UnQual (HsIdent "Int")))
94 simplifiyType (HsTyApp (HsTyApp (HsTyCon (UnQual (HsIdent "Either"))) t1) t2)
95 = liftM2 TEither (simplifiyType t1) (simplifiyType t2)
96 simplifiyType (HsTyApp (HsTyCon (Special HsListCon)) t)
97 = liftM List (simplifiyType t)
99 = throwError ("Unsupported type " ++ show t)
101 quantify :: [TypVar] -> Typ -> Typ
102 quantify special t = foldr allQuant t (nub (listify (\(_::TypVar) -> True) t))
103 where allQuant v | v `elem` special = All v
104 | otherwise = AllStar v