summaryrefslogtreecommitdiff
path: root/src/Language/Fiddle/Internal/UnitInterface.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Language/Fiddle/Internal/UnitInterface.hs')
-rw-r--r--src/Language/Fiddle/Internal/UnitInterface.hs72
1 files changed, 30 insertions, 42 deletions
diff --git a/src/Language/Fiddle/Internal/UnitInterface.hs b/src/Language/Fiddle/Internal/UnitInterface.hs
index b18b98b..4244121 100644
--- a/src/Language/Fiddle/Internal/UnitInterface.hs
+++ b/src/Language/Fiddle/Internal/UnitInterface.hs
@@ -5,15 +5,38 @@ module Language.Fiddle.Internal.UnitInterface where
import Data.Aeson
import Data.Text
import Data.Word
+import GHC.Generics
import Language.Fiddle.Internal.Scopes (Scope)
import Language.Fiddle.Types (SourceSpan)
-data Annotated a = Annotated
- { sourceSpan :: SourceSpan,
- docComment :: Text,
- internal :: a
+-- | Represents a compiler directive that provides configuration for the compiler
+-- or its various backends. Directives can adjust the behavior of the compiler
+-- or influence the code generation in the backends.
+data InternalDirective = InternalDirective
+ { -- | Specifies the backend that this directive is intended for. If 'Nothing',
+ -- the directive applies globally across all backends.
+ directiveBackend :: Maybe String,
+ -- | The key or name of the directive. This identifies the directive's
+ -- purpose, such as enabling specific features or setting options.
+ directiveKey :: String,
+ -- | The optional value associated with this directive. Some directives
+ -- may not require a value (e.g., flags), in which case this field is 'Nothing'.
+ directiveValue :: Maybe String
}
- deriving (Eq, Ord, Show)
+ deriving (Generic, ToJSON, FromJSON, Show, Eq, Ord)
+
+-- | Metadata about an exported value. This includes things like the source
+-- location, doc comments and compiler directives associated with the exported
+-- symbol.
+data Metadata = Metadata
+ { -- | Source location for the exported symbol.
+ metadataSourceSpan :: SourceSpan,
+ -- | Doc comment associated with the symbol.
+ metadataDocComment :: Text,
+ -- | List of directives associated with this exported symbol.
+ metadataDirectives :: [InternalDirective]
+ }
+ deriving (Generic, ToJSON, FromJSON, Show, Eq, Ord)
-- | Contains a datastructure which represents a FiddleUnit.
--
@@ -21,7 +44,7 @@ data Annotated a = Annotated
-- direct dependencies.
data UnitInterface where
UnitInterface ::
- { rootScope :: Scope String (Annotated ExportedValue),
+ { rootScope :: Scope String (Metadata, ExportedValue),
dependencies :: [FilePath]
} ->
UnitInterface
@@ -41,22 +64,7 @@ data ExportedValue where
ExportedObjType ::
{exportObjTypeSize :: Word32} ->
ExportedValue
- deriving (Show, Eq, Ord)
-
-instance (ToJSON a) => ToJSON (Annotated a) where
- toJSON (Annotated span doc internal) =
- object
- [ "sourceSpan" .= span,
- "docComment" .= doc,
- "internal" .= internal
- ]
-
-instance (FromJSON a) => FromJSON (Annotated a) where
- parseJSON = withObject "Annotated" $ \v ->
- Annotated
- <$> v .: "sourceSpan"
- <*> v .: "docComment"
- <*> v .: "internal"
+ deriving (Show, Eq, Ord, Generic, FromJSON, ToJSON)
instance ToJSON UnitInterface where
toJSON (UnitInterface rootScope dependencies) =
@@ -70,23 +78,3 @@ instance FromJSON UnitInterface where
UnitInterface
<$> v .: "rootScope"
<*> v .: "dependencies"
-
-instance ToJSON ExportedValue where
- toJSON (ExportedBitsType size) =
- object
- [ "type" .= String "ExportedBitsType",
- "size" .= size
- ]
- toJSON (ExportedObjType size) =
- object
- [ "type" .= String "ExportedObjType",
- "size" .= size
- ]
-
-instance FromJSON ExportedValue where
- parseJSON = withObject "ExportedValue" $ \v -> do
- typ <- v .: "type"
- case typ of
- String "ExportedBitsType" -> ExportedBitsType <$> v .: "size"
- String "ExportedObjType" -> ExportedObjType <$> v .: "size"
- _ -> fail "Unknown ExportedValue type"