|
@@ -5,6 +5,7 @@ module Gidl.Parse (parseDecls) where
|
|
|
|
|
|
import Control.Applicative ((<$>), (<*>))
|
|
import Control.Applicative ((<$>), (<*>))
|
|
import Control.Monad ((>=>))
|
|
import Control.Monad ((>=>))
|
|
|
|
+import Control.Monad.Reader (ask, lift, local, runReaderT)
|
|
import Data.List (partition, group, intercalate)
|
|
import Data.List (partition, group, intercalate)
|
|
import Data.SCargot.Comments (withHaskellComments)
|
|
import Data.SCargot.Comments (withHaskellComments)
|
|
import Data.SCargot.General ( SExprSpec
|
|
import Data.SCargot.General ( SExprSpec
|
|
@@ -52,7 +53,7 @@ toEnv decls = do
|
|
unlessEmpty (duplicated interfaceNames)
|
|
unlessEmpty (duplicated interfaceNames)
|
|
(\n -> "Interface named '" ++ n ++ "' declared multiple times")
|
|
(\n -> "Interface named '" ++ n ++ "' declared multiple times")
|
|
|
|
|
|
- typs <- mapM (getTypePair . getName) typDs
|
|
|
|
|
|
+ typs <- mapM (flip runReaderT [] . getTypePair . getName) typDs
|
|
ifcs <- mapM getIfacePair interfaceNames
|
|
ifcs <- mapM getIfacePair interfaceNames
|
|
return (TypeEnv typs, InterfaceEnv ifcs)
|
|
return (TypeEnv typs, InterfaceEnv ifcs)
|
|
where (typDs, ifcDs) = partition isTypeDecl decls
|
|
where (typDs, ifcDs) = partition isTypeDecl decls
|
|
@@ -67,48 +68,53 @@ toEnv decls = do
|
|
ifcMap = [(getName i, toInterface i) | i <- ifcDs]
|
|
ifcMap = [(getName i, toInterface i) | i <- ifcDs]
|
|
|
|
|
|
-- this is gross because I'm trying to make sure declarations
|
|
-- this is gross because I'm trying to make sure declarations
|
|
- -- can happen in any order. XXX: prevent recursion!
|
|
|
|
|
|
+ -- can happen in any order.
|
|
getType n = snd `fmap` getTypePair n
|
|
getType n = snd `fmap` getTypePair n
|
|
- getTypePair n = case lookup n typMap of
|
|
|
|
- Just (Right t) -> return t
|
|
|
|
- Just (Left l) -> Left l
|
|
|
|
- Nothing -> throw ("Unknown primitive type: " ++ n)
|
|
|
|
|
|
+ getTypePair n = do
|
|
|
|
+ env <- ask
|
|
|
|
+ if n `elem` env
|
|
|
|
+ then lift $ throw ("Types cannot be recursive.\n" ++
|
|
|
|
+ showCycle env)
|
|
|
|
+ else case lookup n typMap of
|
|
|
|
+ Just rs -> rs
|
|
|
|
+ Nothing -> lift $ throw ("Unknown primitive type: " ++ n)
|
|
|
|
|
|
getIface n = snd `fmap` getIfacePair n
|
|
getIface n = snd `fmap` getIfacePair n
|
|
getIfacePair n = case lookup n ifcMap of
|
|
getIfacePair n = case lookup n ifcMap of
|
|
Just (Right i) -> return i
|
|
Just (Right i) -> return i
|
|
Just (Left l) -> Left l
|
|
Just (Left l) -> Left l
|
|
- Nothing -> throw ("Unknown interface: " ++ n)
|
|
|
|
|
|
+ Nothing -> Left ("Unknown interface: " ++ n)
|
|
|
|
|
|
getPrimType n = do
|
|
getPrimType n = do
|
|
t <- getType n
|
|
t <- getType n
|
|
case t of
|
|
case t of
|
|
PrimType t' -> return t'
|
|
PrimType t' -> return t'
|
|
- _ -> throw ("Expected primitive type but got " ++ show t)
|
|
|
|
|
|
+ _ -> lift $ throw ("Expected primitive type but got " ++ show t)
|
|
|
|
|
|
-- converts a decl to an actual type
|
|
-- converts a decl to an actual type
|
|
- toType (NewtypeDecl n t) = do
|
|
|
|
|
|
+ toType (NewtypeDecl n t) = local (n:) $ do
|
|
t' <- getPrimType t
|
|
t' <- getPrimType t
|
|
return (n, PrimType (Newtype n t'))
|
|
return (n, PrimType (Newtype n t'))
|
|
- toType (EnumDecl (n, s) ts) = do
|
|
|
|
- unlessEmpty (duplicated (map fst ts))
|
|
|
|
|
|
+ toType (EnumDecl (n, s) ts) = local (n:) $ do
|
|
|
|
+ lift $ unlessEmpty (duplicated (map fst ts))
|
|
(\i -> "Enum identifier '" ++ i
|
|
(\i -> "Enum identifier '" ++ i
|
|
++ "' repeated in declaration of 'Enum " ++ n ++ "'")
|
|
++ "' repeated in declaration of 'Enum " ++ n ++ "'")
|
|
- unlessEmpty (duplicated (map snd ts))
|
|
|
|
|
|
+ lift $ unlessEmpty (duplicated (map snd ts))
|
|
(\i -> "Enum value '" ++ (show i)
|
|
(\i -> "Enum value '" ++ (show i)
|
|
++ "' repeated in declaration of 'Enum " ++ n ++ "'")
|
|
++ "' repeated in declaration of 'Enum " ++ n ++ "'")
|
|
return (n, PrimType (EnumType n s ts))
|
|
return (n, PrimType (EnumType n s ts))
|
|
- toType (StructDecl n ss) = do
|
|
|
|
|
|
+ toType (StructDecl n ss) = local (n:) $ do
|
|
ps <- mapM (getPrimType . snd) ss
|
|
ps <- mapM (getPrimType . snd) ss
|
|
return (n, StructType n (zip (map fst ss) ps))
|
|
return (n, StructType n (zip (map fst ss) ps))
|
|
toType _ = error "[unreachable]"
|
|
toType _ = error "[unreachable]"
|
|
|
|
|
|
toMethod (n, AttrDecl perm t) = do
|
|
toMethod (n, AttrDecl perm t) = do
|
|
- t' <- getType t
|
|
|
|
|
|
+ t' <- runReaderT (getType t) []
|
|
return (n, AttrMethod perm t')
|
|
return (n, AttrMethod perm t')
|
|
|
|
+
|
|
toMethod (n, StreamDecl t) = do
|
|
toMethod (n, StreamDecl t) = do
|
|
- t' <- getType t
|
|
|
|
- return (n, StreamMethod 0 t') -- XXX
|
|
|
|
|
|
+ t' <- runReaderT (getType t) []
|
|
|
|
+ return (n, StreamMethod 0 t')
|
|
|
|
|
|
toInterface (InterfaceDecl n is ms) = do
|
|
toInterface (InterfaceDecl n is ms) = do
|
|
ms' <- mapM toMethod ms
|
|
ms' <- mapM toMethod ms
|
|
@@ -124,6 +130,12 @@ toEnv decls = do
|
|
isTypeDecl InterfaceDecl {} = False
|
|
isTypeDecl InterfaceDecl {} = False
|
|
isTypeDecl _ = True
|
|
isTypeDecl _ = True
|
|
|
|
|
|
|
|
+ showCycle [] = error "[unreachable]"
|
|
|
|
+ showCycle [x] = " In recursive type `" ++ x ++ "`"
|
|
|
|
+ showCycle ls@(x:_) = " In mutually recursive cycle " ++ go ls
|
|
|
|
+ where go (y:ys) = "`" ++ y ++ "` => " ++ go ys
|
|
|
|
+ go [] = "`" ++ x ++ "`"
|
|
|
|
+
|
|
parseDecls :: String -> Either String (TypeEnv, InterfaceEnv)
|
|
parseDecls :: String -> Either String (TypeEnv, InterfaceEnv)
|
|
parseDecls = return . pack >=> decode gidlSpec >=> toEnv
|
|
parseDecls = return . pack >=> decode gidlSpec >=> toEnv
|
|
|
|
|