summaryrefslogtreecommitdiff
path: root/src/Language/Fiddle/Ast/Internal/SyntaxTree.hs
diff options
context:
space:
mode:
authorJosh Rahm <joshuarahm@gmail.com>2024-09-27 16:20:32 -0600
committerJosh Rahm <joshuarahm@gmail.com>2024-09-27 16:24:10 -0600
commit21e6e5940ecb462436b8dc94428c5cee5cdc9072 (patch)
tree01405c637f904f24feadc177a84ab9bae7c8c99c /src/Language/Fiddle/Ast/Internal/SyntaxTree.hs
parenta4cffc1eeb547f780068875a703251db6aa41d6c (diff)
downloadfiddle-21e6e5940ecb462436b8dc94428c5cee5cdc9072.tar.gz
fiddle-21e6e5940ecb462436b8dc94428c5cee5cdc9072.tar.bz2
fiddle-21e6e5940ecb462436b8dc94428c5cee5cdc9072.zip
Add import resolution phase and also add a more abstractions around
compliation phases.
Diffstat (limited to 'src/Language/Fiddle/Ast/Internal/SyntaxTree.hs')
-rw-r--r--src/Language/Fiddle/Ast/Internal/SyntaxTree.hs50
1 files changed, 25 insertions, 25 deletions
diff --git a/src/Language/Fiddle/Ast/Internal/SyntaxTree.hs b/src/Language/Fiddle/Ast/Internal/SyntaxTree.hs
index d03a855..c37be87 100644
--- a/src/Language/Fiddle/Ast/Internal/SyntaxTree.hs
+++ b/src/Language/Fiddle/Ast/Internal/SyntaxTree.hs
@@ -9,7 +9,7 @@
module Language.Fiddle.Ast.Internal.SyntaxTree
( -- Type Families
NumberType,
- ImportType,
+ ImportInterface,
-- Witness Types
Witness (..),
WitnessType,
@@ -68,23 +68,21 @@ import Language.Fiddle.Ast.Internal.Generic
import Language.Fiddle.Ast.Internal.Instances
import Language.Fiddle.Ast.Internal.Kinds
import Language.Fiddle.Ast.Internal.Stage
+import Language.Fiddle.Internal.UnitInterface (UnitInterface)
--- The Type of number during each stage of compilation. When in the first stage,
+-- | The Type of number during each stage of compilation. When in the first stage,
-- numbers are just strings like anything else. In later stages, numbers get
-- parsed into actual integers. This makes it easier to process later.
type family NumberType (a :: Stage) :: Type where
NumberType s = If (s < Expanded) Text Integer
--- The type that represents an import statement. In the early stages of
--- compilation, this is just a string representing the import path, but in later
--- stages of compilation, this actually gets replaced by an abstract
--- representation of the imported material.
-type family ImportType (stage :: Stage) :: SynTree where
- ImportType Parsed = ImportStatement
- ImportType Expanded = ImportStatement
- ImportType Checked = ImportStatement
+-- | The type used for ImportInterfaces attached to ImportStatements. Before import
+-- resolution, this type is just '()', but when imports are resolved, it turns
+-- into a 'UnitInterface'.
+type family ImportInterface (stage :: Stage) :: Type where
+ ImportInterface s = If (s < ImportsResolved) () UnitInterface
--- A way to disable or enable a subtree type based on a type-level boolean.
+-- | A way to disable or enable a subtree type based on a type-level boolean.
--
-- This is used over GADT's specific parameterization to allow for deriving
-- generics and reduce boilerplate.
@@ -225,9 +223,7 @@ data FiddleUnit (stage :: Stage) (f :: Type -> Type) a where
fiddleUnitAnnot :: a
} ->
FiddleUnit stage f a
- deriving (Generic, Annotated, Typeable)
-
-deriving instance (Alter (ImportType stage)) => Alter (FiddleUnit stage)
+ deriving (Generic, Annotated, Typeable, Alter)
-- | Represents an identifier with an associated annotation.
data Identifier f a = Identifier
@@ -259,16 +255,19 @@ data Expression (s :: Stage) :: SynTree where
deriving (Generic, Annotated, Alter, Typeable)
-- | Represents an import statement in the Fiddle language.
-data ImportStatement f a where
+data ImportStatement stage f a where
ImportStatement ::
{ -- | The path to import.
importPath :: Text,
-- | Optional list of imported items.
importList :: Maybe (ImportList f a),
+
+ importInterface :: ImportInterface stage,
+
-- | Annotation for the import statement.
importStatementAnnot :: a
} ->
- ImportStatement f a
+ ImportStatement stage f a
deriving (Generic, Annotated, Alter, Typeable)
-- | A list of imported identifiers.
@@ -297,7 +296,12 @@ data FiddleDecl :: StagedSynTree where
-- | An import declaration.
ImportDecl ::
{ -- | The imported type.
- importType :: ImportType stage f a,
+ importStatement :: ImportStatement stage f a,
+
+ -- | The interface for this imported file. This type depends on the stage
+ -- of compilation. Initially it's just '()', but will eventually be resolved
+ -- into a 'UnitInterface'.
+
-- | Annotation for the import declaration.
importDeclAnnot :: a
} ->
@@ -362,9 +366,7 @@ data FiddleDecl :: StagedSynTree where
objectAnnot :: a
} ->
FiddleDecl stage f a
- deriving (Generic, Annotated, Typeable)
-
-deriving instance (Alter (ImportType stage)) => Alter (FiddleDecl stage)
+ deriving (Generic, Annotated, Alter, Typeable)
-- | Represents the body of an object type, containing a body type (struct or
-- union), a list of object declarations, and an annotation.
@@ -386,7 +388,7 @@ data ObjType stage f a where
-- | An anonymous object type, allowed only in Parsed.
AnonymousObjType ::
{ -- | Witness for stage constraint.
- anonWitness :: Witness (stage == Parsed),
+ anonWitness :: Witness (stage < Expanded),
-- | The body of the anonymous type.
anonBody :: f (ObjTypeBody stage f a),
-- | Annotation for the anonymous type.
@@ -573,7 +575,7 @@ data RegisterBitsTypeRef stage f a where
-- | An anonymous type for register bits, used in Parsed.
RegisterBitsAnonymousType ::
{ -- | Witness for stage constraint.
- anonBitsWitness :: Witness (stage == Parsed),
+ anonBitsWitness :: Witness (stage < Expanded),
-- | The anonymous type.
anonBitsType :: AnonymousBitsType stage f a,
-- | Annotation for the anonymous type.
@@ -667,9 +669,7 @@ data PackageBody (stage :: Stage) (f :: Type -> Type) a where
packageBodyAnnot :: a
} ->
PackageBody stage f a
- deriving (Generic, Annotated, Typeable)
-
-deriving instance (Alter (ImportType stage)) => Alter (PackageBody stage)
+ deriving (Generic, Annotated, Typeable, Alter)
squeeze :: (Alter t, Traversable f, Monad f) => t f a -> f (t Identity a)
squeeze = alter (fmap Identity) return