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.hs58
1 files changed, 58 insertions, 0 deletions
diff --git a/src/Language/Fiddle/Internal/UnitInterface.hs b/src/Language/Fiddle/Internal/UnitInterface.hs
index 1f12c4c..b18b98b 100644
--- a/src/Language/Fiddle/Internal/UnitInterface.hs
+++ b/src/Language/Fiddle/Internal/UnitInterface.hs
@@ -1,5 +1,8 @@
+{-# LANGUAGE OverloadedStrings #-}
+
module Language.Fiddle.Internal.UnitInterface where
+import Data.Aeson
import Data.Text
import Data.Word
import Language.Fiddle.Internal.Scopes (Scope)
@@ -24,6 +27,13 @@ data UnitInterface where
UnitInterface
deriving (Eq, Ord, Show)
+instance Semigroup UnitInterface where
+ (<>) (UnitInterface s d) (UnitInterface s1 d1) =
+ UnitInterface (s <> s1) (d <> d1)
+
+instance Monoid UnitInterface where
+ mempty = UnitInterface mempty mempty
+
data ExportedValue where
ExportedBitsType ::
{exportBitsTypeSize :: Word32} ->
@@ -32,3 +42,51 @@ data ExportedValue where
{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"
+
+instance ToJSON UnitInterface where
+ toJSON (UnitInterface rootScope dependencies) =
+ object
+ [ "rootScope" .= rootScope,
+ "dependencies" .= dependencies
+ ]
+
+instance FromJSON UnitInterface where
+ parseJSON = withObject "UnitInterface" $ \v ->
+ 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"