Browse Source

gidl: support enum widths, some ast parsing checks

Pat Hickey 10 years ago
parent
commit
30e97b9a87
4 changed files with 33 additions and 44 deletions
  1. 20 5
      src/Gidl/Parse.hs
  2. 0 0
      src/Gidl/Types/AST.hs
  3. 5 38
      tests/Test.hs
  4. 8 1
      tests/testtypes.sexpr

+ 20 - 5
src/Gidl/Parse.hs

@@ -1,6 +1,7 @@
 
 module Gidl.Parse where
 
+import Data.List
 import Data.Functor.Identity
 import Control.Monad
 import Text.Parsec.Prim
@@ -142,12 +143,25 @@ tEnumDecl = tList $ do
   tIdentifier "def-enum"
   tWhiteSpace
   n <- tSymbol
-  -- XXX specify bit width, optionally
+  w  <- optionMaybe (try tInteger)
+  width <- case w of
+    Nothing -> return Bits32
+    Just 8 -> return  Bits8
+    Just 16 -> return Bits16
+    Just 32 -> return Bits32
+    Just 64 -> return Bits64
+    _ -> fail "Expected enum bit size to be 8, 16, 32, or 64"
+
   vs <- tList $ many1 $ tPair tSymbol tNatural
-  -- XXX check that symbols are unique, numbers are unique, numbers are
-  -- ascending
+  when (not_unique (map fst vs)) $
+    fail "enum keys were not unique"
+  when (not_unique (map snd vs)) $
+    fail "enum values were not unique"
   -- XXX make it possible to implicitly assign numbers
-  return (n, EnumType (EnumT Bits32 vs))
+  return (n, EnumType (EnumT width vs))
+
+not_unique :: (Eq a) => [a] -> Bool
+not_unique l = nub l /= l
 
 tPermission :: Parser a Perm
 tPermission = do
@@ -197,7 +211,8 @@ tInterfaceDecl = tList $ do
   n <- tSymbol
   tWhiteSpace
   ms <- tList (many1 tInterfaceMethod)
-  -- XXX require the names to be unique
+  when (not_unique (map fst ms)) $
+    fail "expected unique interface method names"
   tWhiteSpace
   ps <- optionMaybe (tList (many1 tKnownInterfaceName))
   -- XXX require the ms not shadow names in inherited interfaces

+ 0 - 0
src/Gidl/Types/AST.hs

@@ -15,8 +15,6 @@ data Type
   | NewtypeType Newtype
   | EnumType EnumT
   | AtomType Atom
   deriving (Eq, Show)
 
 data Atom

+ 5 - 38
tests/Test.hs

@@ -9,41 +9,8 @@ main = test "tests/testtypes.sexpr"
 test :: FilePath -> IO ()
 test f = do
   c <- readFile f
-  print $ parseDecls c
---- below is just a stash
-
-hb_t :: Type
-hb_t = StructType $ Struct
-          [ ("mode", "mode_t")
-          , ("time", "time_micros_t")
-          ]
-
-mode_t :: Type
-mode_t = StructType $ Struct
-          [ ("armed", "bool_t")
-          , ("controlsource", "controlsource_t" )
-          ]
-
-controlsource_t :: Type
-controlsource_t = EnumType $ EnumT Bits8
-  [ ("manual", 0)
-  , ("auto", 1)
-  ]
-
-time_micros_t :: Type
-time_micros_t = NewtypeType $ Newtype "uint8_t"
-
-typeEnv' :: TypeEnv
-typeEnv' = TypeEnv
-  [ ("hb_t", hb_t)
-  , ("mode_t", mode_t)
-  , ("controlsource_t", controlsource_t)
-  , ("time_micros_t", time_micros_t)
-  ]
-
-
-data Sys = Sys TypeEnv Streams Attrs
-
-data Attrs = Attrs [(String, Either Type Attrs)]
-
-data Streams = Streams [(String, Type)]
+  case parseDecls c of
+    Left e -> print e
+    Right (te, ie) -> do
+      print te
+      print ie

+ 8 - 1
tests/testtypes.sexpr

@@ -3,7 +3,14 @@
 
 -- comments should be haskell style, because we're suing parsec's haskell lexer
 
-(def-enum armed_t
+-- enums default to 32 bit width if you don't really care
+(def-enum mode_t
+ ((stabilize 0)
+  (auto 1)))
+
+-- or you can specify a width
+(def-enum armed_t 
+ 8
  ((disarmed 0)
   (armed 1)))