summaryrefslogtreecommitdiff
path: root/src/Language/Fiddle/Ast.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Language/Fiddle/Ast.hs')
-rw-r--r--src/Language/Fiddle/Ast.hs21
1 files changed, 16 insertions, 5 deletions
diff --git a/src/Language/Fiddle/Ast.hs b/src/Language/Fiddle/Ast.hs
index bb6605e..8680790 100644
--- a/src/Language/Fiddle/Ast.hs
+++ b/src/Language/Fiddle/Ast.hs
@@ -11,6 +11,7 @@ module Language.Fiddle.Ast where
import Data.Functor.Identity
import Data.Kind (Type)
+import Data.List.NonEmpty
import Data.Proxy
import Data.Text (Text)
import Data.Traversable
@@ -47,6 +48,16 @@ type family ImportType (stage :: Stage) :: SynTreeKind where
ImportType Stage2 = ImportStatement
ImportType Stage3 = ImportStatement
+-- Type-level constraint to determine if a stage is less than some natural
+-- ordinal. Used to bound parts of the AST in multiple stages.
+type StageLessThan stage (n :: Natural) = (CmpNat (StageNumber stage) n ~ LT)
+
+-- A Name is multiple identifiers separated by dots. It's the way of namespaces
+-- to different packages.
+data Name f a where
+ Name :: NonEmpty (Identifier f a) -> a -> Name f a
+ deriving (Generic, Annotated, Alter, Typeable)
+
-- [[packed, rust: name="field_name"]]
data Directive f a where
Directive :: f (DirectiveBody f a) -> a -> Directive f a
@@ -146,9 +157,11 @@ data FiddleDecl (stage :: Stage) (f :: Type -> Type) a where
ImportType stage f a ->
a ->
FiddleDecl stage f a
+ UsingDecl ::
+ Name f a -> a -> FiddleDecl stage f a
{- Package Statement. Package Name, Package body -}
PackageDecl ::
- Identifier f a ->
+ Name f a ->
f (PackageBody stage f a) ->
a ->
FiddleDecl stage f a
@@ -197,11 +210,9 @@ data ObjType stage f a where
-- <type>[<expr>]
ArrayObjType :: ObjType stage f a -> Expression stage f a -> a -> ObjType stage f a
-- <identifier>
- ReferencedObjType :: Identifier f a -> a -> ObjType stage f a
+ ReferencedObjType :: Name f a -> a -> ObjType stage f a
deriving (Typeable)
-type StageLessThan stage (n :: Natural) = (CmpNat (StageNumber stage) n ~ LT)
-
data ObjTypeDecl stage f a where
{- assert_pos(<expr>) -}
AssertPosStatement ::
@@ -278,7 +289,7 @@ data RegisterBitsTypeRef stage f a where
a ->
RegisterBitsTypeRef stage f a
{- Reference to a type. -}
- RegisterBitsReference :: Identifier f a -> a -> RegisterBitsTypeRef stage f a
+ RegisterBitsReference :: Name f a -> a -> RegisterBitsTypeRef stage f a
{- enum(<expr>) { <body> }
Anonymous types are only allowed in stage1.
Stage2 should de-anonymize these type. -}