betere gamma
[cc1516.git] / sem.icl
1 implementation module sem
2
3 import qualified Data.Map as Map
4 from Data.Func import $
5 import Data.Maybe
6 import Data.Either
7 import Data.Functor
8 import Control.Applicative
9 import Control.Monad
10 import Control.Monad.State
11 import Control.Monad.Identity
12 import Math.Random
13 import StdMisc
14 from StdFunc import id, const, o
15 import StdString
16 import StdTuple
17 import StdList
18
19 from Text import class Text(concat), instance Text String
20
21 import AST
22 from parse import :: ParserOutput, :: Error
23
24 :: Gamma :== ('Map'.Map String Type, [String])
25 :: Env a :== (State Gamma (Either SemError a))
26
27 get = state $ \s -> (s,s)
28
29 getRandomStream :: Int -> [String]
30 getRandomStream i = genIdents $ filter (isAlpha o toChar) (genRandInt i)
31 where
32 genIdents r = let (ic, r) = splitAt 5 r in [toString ic: genIdents r]
33
34 freshIdent :: Gamma -> (String, Gamma)
35 freshIdent (st, [ident:rest]) = case 'Map'.get ident st of
36 Nothing = (ident, (st, rest))
37 _ = freshIdent (st, rest)
38
39 putIdent :: String Type -> Env Void
40 putIdent i t = gets (\(st, r)->'Map'.get i st) >>= \mt -> case mt of
41 Nothing = pure <$> modify (\(st, r)->('Map'.put i t st, r))
42 Just t2 = unify t t2 >>= \r -> case r of
43 Left e = pure $ Left e
44 Right t3 = pure <$> modify (\(st, r)->('Map'.put i t3 st, r))
45
46 instance toString SemError where
47 toString (ParseError p e) = concat [
48 toString p,"SemError: ParseError: ", e]
49 toString (Error e) = "SemError: " +++ e
50 toString (UnifyErrorStub t1 t2) = toString (UnifyError {line=0,col=0} t1 t2)
51 toString (UnifyError p t1 t2) = concat [
52 toString p,
53 "SemError: Cannot unify types. Expected: ",
54 toString t1, ". Given: ", toString t2]
55
56 sem :: AST -> SemOutput
57 sem (AST vd fd)
58 # (eithervds, gamma) = runState (mapM semVarDecl vd) ('Map'.newMap, getRandomStream 0)
59 # (eitherfds, gamma) = runState (mapM semFunDecl fd) gamma
60 = case splitEithers eithervds of
61 (Left errs) = Left $ errs ++ [x\\(Left x)<-eitherfds]
62 (Right vds) = case splitEithers eitherfds of
63 (Left errs) = Left errs
64 (Right fds) = Right $ AST vds fds
65
66 splitEithers :: [Either a b] -> Either [a] [b]
67 splitEithers [] = Right []
68 splitEithers [Right x:xs] = splitEithers xs >>= \rest->Right [x:rest]
69 splitEithers xs = Left $ [x\\(Left x)<-xs]
70
71 semFunDecl :: FunDecl -> Env FunDecl
72 semFunDecl f = pure $ Right f
73
74 semVarDecl :: VarDecl -> Env VarDecl
75 semVarDecl vd=:(VarDecl pos type ident ex) = unify type ex
76 >>= \et->case et of
77 Left err = pure $ Left err
78 Right t = putIdent ident t >>| pure (Right $ VarDecl pos t ident ex)
79
80 typeExpr :: Expr -> Env Type
81 typeExpr (IntExpr _ _) = pure $ Right IntType
82 typeExpr (CharExpr _ _) = pure $ Right CharType
83 typeExpr (BoolExpr _ _) = pure $ Right BoolType
84 typeExpr (Op1Expr p UnNegation expr) = unify BoolType expr
85 typeExpr (Op1Expr p UnMinus expr) = unify IntType expr
86 typeExpr (TupleExpr p (e1, e2)) = typeExpr e1
87 >>= \ete1->typeExpr e2 >>= \ete2->pure (
88 ete1 >>= \te1->ete2 >>= \te2->Right $ TupleType (te1, te2))
89 //Int
90 typeExpr (Op2Expr p e1 BiPlus e2) = unify IntType e1 >>| unify IntType e2
91 typeExpr (Op2Expr p e1 BiMinus e2) = unify IntType e1 >>| unify IntType e2
92 typeExpr (Op2Expr p e1 BiTimes e2) = unify IntType e1 >>| unify IntType e2
93 typeExpr (Op2Expr p e1 BiDivide e2) = unify IntType e1 >>| unify IntType e2
94 typeExpr (Op2Expr p e1 BiMod e2) = unify IntType e1 >>| unify IntType e2
95 //bool, char of int
96 typeExpr (Op2Expr p e1 BiEquals e2) = undef
97 typeExpr (Op2Expr p e1 BiUnEqual e2) = undef
98 //char of int
99 typeExpr (Op2Expr p e1 BiLesser e2) = undef
100 typeExpr (Op2Expr p e1 BiGreater e2) = undef
101 typeExpr (Op2Expr p e1 BiLesserEq e2) = undef
102 typeExpr (Op2Expr p e1 BiGreaterEq e2) = undef
103 //bool
104 typeExpr (Op2Expr p e1 BiAnd e2) = undef
105 typeExpr (Op2Expr p e1 BiOr e2) = undef
106 //a
107 typeExpr (Op2Expr p e1 BiCons e2) = undef
108 //typeExpr (FunExpr Pos FunCall) = undef
109 //typeExpr (EmptyListExpr Pos) = undef
110 //typeExpr (VarExpr Pos VarDef) = undef //when checking var-expr, be sure to
111 //put the infered type
112 //in the context
113
114 class unify a :: Type a -> Env Type
115
116 instance unify Expr where
117 unify (_ ->> _) e = pure $ Left $ ParseError (extrPos e)
118 "Expression cannot be a higher order function. Yet..."
119 unify VoidType e = pure $ Left $ ParseError (extrPos e)
120 "Expression cannot be a Void type."
121 unify (IdType _) e = pure $ Left $ ParseError (extrPos e)
122 "Expression cannot be an polymorf type."
123 unify VarType e = typeExpr e
124 unify t e = typeExpr e
125 >>= \eithertype->case eithertype of
126 Left e = pure $ Left e
127 Right tex = unify t tex >>= \eitherun->case eitherun of
128 Left err = pure $ Left $ decErr e err
129 Right t = pure $ Right t
130
131 instance unify Type where
132 unify IntType IntType = pure $ Right IntType
133 unify BoolType BoolType = pure $ Right BoolType
134 unify CharType CharType = pure $ Right CharType
135 unify t1 t2 = pure $ Left $ UnifyError zero t1 t2
136
137 instance zero Pos where
138 zero = {line=0,col=0}
139
140 decErr :: Expr SemError -> SemError
141 decErr e (UnifyError _ t1 t2) = UnifyError (extrPos e) t1 t2
142 decErr e (ParseError _ s) = ParseError (extrPos e) s
143 decErr e err = err
144
145 extrPos :: Expr -> Pos
146 extrPos (VarExpr p _) = p
147 extrPos (Op2Expr p _ _ _) = p
148 extrPos (Op1Expr p _ _) = p
149 extrPos (IntExpr p _) = p
150 extrPos (CharExpr p _) = p
151 extrPos (BoolExpr p _) = p
152 extrPos (FunExpr p _) = p
153 extrPos (EmptyListExpr p) = p
154 extrPos (TupleExpr p _) = p