summaryrefslogtreecommitdiff
path: root/src/Language/Fiddle/Internal/UnitInterface.hs
blob: 42441218d0b5cad553edcc7165ef804d577bd68a (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
{-# LANGUAGE OverloadedStrings #-}

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)

-- | 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 (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.
--
-- These datastructures contain the exported symobls of a fiddle unit and it's
-- direct dependencies.
data UnitInterface where
  UnitInterface ::
    { rootScope :: Scope String (Metadata, ExportedValue),
      dependencies :: [FilePath]
    } ->
    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} ->
    ExportedValue
  ExportedObjType ::
    {exportObjTypeSize :: Word32} ->
    ExportedValue
  deriving (Show, Eq, Ord, Generic, FromJSON, ToJSON)

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"