summaryrefslogtreecommitdiff
path: root/src/Language/Fiddle/Compiler/Backend.hs
blob: dff8e47e08d1c39f68d1f2007da3d0801f22eae9 (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
module Language.Fiddle.Compiler.Backend where

import Control.Monad (forM_)
import Control.Monad.Identity (Identity)
import Control.Monad.Writer
import Data.Map (Map)
import qualified Data.Text.IO
import qualified Data.Map as Map
import Data.Text (Text)
import Language.Fiddle.Ast
import Language.Fiddle.Types (Commented, SourceSpan)
import Options.Applicative

-- | Data representing the result of transpilation.
data TranspileResult where
  TranspileResult ::
    { newFileContents :: Map FilePath Text
    } ->
    TranspileResult

instance Semigroup TranspileResult where
  (<>) (TranspileResult c1) (TranspileResult c2) =
    TranspileResult $ Map.unionWith (<>) c1 c2

instance Monoid TranspileResult where
  mempty = TranspileResult mempty

-- | A backend for the FiddleCompiler. Takes a Checked FiddleUnit and emits
-- generated code for that fiddle unit.
data Backend where
  Backend ::
    forall privateFlags privateState.
    { backendName :: String,
      backendOptionsParser :: Parser privateFlags,
      backendIOMakeState :: privateFlags -> IO privateState,
      backendTranspile ::
        privateFlags ->
        privateState ->
        FiddleUnit Checked Identity (Commented SourceSpan) ->
        TranspileResult
    } ->
    Backend

backendToParserFunction ::
  Backend ->
  Parser
    ( FiddleUnit Checked Identity (Commented SourceSpan) -> IO TranspileResult
    )
backendToParserFunction
  Backend
    { backendOptionsParser = optionsParser,
      backendIOMakeState = ioMakeState,
      backendTranspile = transpile
    } =
    ( \opts ->
        let ioState = ioMakeState opts
         in \fiddleUnit -> do
              state <- ioState
              return $ transpile opts state fiddleUnit
    )
      <$> optionsParser

processTranspileResult :: TranspileResult -> IO ()
processTranspileResult (TranspileResult mp) =
  forM_ (Map.toList mp) $ \(file, text) -> do
    Data.Text.IO.writeFile file text

nullBackend :: Backend
nullBackend = Backend {
  backendName = "null",
  backendOptionsParser = pure (),
  backendIOMakeState = const $ return (),
  backendTranspile = \_ _ _ -> mempty 
}