import Control.Monad
import Control.Monad.State
import Control.Monad.Identity
+import Math.Random
+ import Control.Monad.Trans
import StdMisc
-from StdFunc import id, const
+from StdFunc import id, const, o
import StdString
+import StdTuple
import StdList
from Text import class Text(concat), instance Text String
import AST
from parse import :: ParserOutput, :: Error
-:: Gamma :== 'Map'.Map String Type
+:: Gamma :== ('Map'.Map String Type, [String])
- :: Env a :== (State Gamma (Either SemError a))
+ :: Env a :== StateT Gamma (Either SemError) a
- get = state $ \s -> (s,s)
+ //we need to redefine this even though it is in Control.Monad.State
+ instance MonadTrans (StateT Gamma) where
+ liftT m = StateT \s-> m >>= \a-> return (a, s)
+
+ get = gets id
-instance toString SemError where
- toString (ParseError p e) = concat [
- toString p,"SemError: ParseError: ", e]
- toString (Error e) = "SemError: " +++ e
- toString (UnifyErrorStub t1 t2) = toString (UnifyError {line=0,col=0} t1 t2)
- toString (UnifyError p t1 t2) = concat [
- toString p,
- "SemError: Cannot unify types. Expected: ",
- toString t1, ". Given: ", toString t2]
+getRandomStream :: Int -> [String]
+getRandomStream i = genIdents $ filter (isAlpha o toChar) (genRandInt i)
+ where
+ genIdents r = let (ic, r) = splitAt 5 r in [toString ic: genIdents r]
+
+freshIdent :: Gamma -> (String, Gamma)
+freshIdent (st, [ident:rest]) = case 'Map'.get ident st of
+ Nothing = (ident, (st, rest))
+ _ = freshIdent (st, rest)
putIdent :: String Type -> Env Void
-putIdent i t = gets ('Map'.get i) >>= \mt -> case mt of
- Nothing = modify ('Map'.put i t)
- Just t2 = unify t t2 >>= \t3-> modify ('Map'.put i t3)
+putIdent i t = gets (\(st, r)->'Map'.get i st) >>= \mt -> case mt of
- Nothing = pure <$> modify (\(st, r)->('Map'.put i t st, r))
- Just t2 = unify t t2 >>= \r -> case r of
- Left e = pure $ Left e
- Right t3 = pure <$> modify (\(st, r)->('Map'.put i t3 st, r))
++ Nothing = modify (\(st, r)->('Map'.put i t st, r))
++ Just t2 = unify t t2 >>= \t3-> modify (\(st, r)->('Map'.put i t3 st, r))
+
+instance toString SemError where
+ toString (ParseError p e) = concat [
+ toString p,"SemError: ParseError: ", e]
+ toString (Error e) = "SemError: " +++ e
+ toString (UnifyErrorStub t1 t2) = toString (UnifyError {line=0,col=0} t1 t2)
+ toString (UnifyError p t1 t2) = concat [
+ toString p,
+ "SemError: Cannot unify types. Expected: ",
+ toString t1, ". Given: ", toString t2]
sem :: AST -> SemOutput
- sem (AST vd fd)
- # (eithervds, gamma) = runState (mapM semVarDecl vd) ('Map'.newMap, getRandomStream 0)
- # (eitherfds, gamma) = runState (mapM semFunDecl fd) gamma
- = case splitEithers eithervds of
- (Left errs) = Left $ errs ++ [x\\(Left x)<-eitherfds]
- (Right vds) = case splitEithers eitherfds of
- (Left errs) = Left errs
- (Right fds) = Right $ AST vds fds
-sem (AST vd fd) = case evalStateT m 'Map'.newMap of
++sem (AST vd fd) = case evalStateT m ('Map'.newMap, getRandomStream 0) of
+ Left e = Left [e]
+ Right (vds, fds) = Right (AST vds fds)
+ where
+ m :: Env (([VarDecl], [FunDecl]))
+ m = (mapM semVarDecl vd) >>= \vds ->
+ mapM semFunDecl fd >>= \fds ->
+ pure (vds, fds)
+
++
+
splitEithers :: [Either a b] -> Either [a] [b]
splitEithers [] = Right []
splitEithers [Right x:xs] = splitEithers xs >>= \rest->Right [x:rest]