{-# LANGUAGE OverloadedStrings #-}

-- | C code generator.  This module can convert a correct ImpCode
-- program to an equivalent C program.  This C program is expected to
-- be converted to WebAssembly, so we also produce the intended
-- JavaScript wrapper.
module Futhark.CodeGen.Backends.SequentialWASM
  ( compileProg,
    runServer,
    libraryExports,
    GC.CParts (..),
    GC.asLibrary,
    GC.asExecutable,
    GC.asServer,
  )
where

import Data.Maybe
import qualified Data.Text as T
import qualified Futhark.CodeGen.Backends.GenericC as GC
import Futhark.CodeGen.Backends.GenericWASM
import Futhark.CodeGen.Backends.SequentialC.Boilerplate
import qualified Futhark.CodeGen.ImpCode.Sequential as Imp
import qualified Futhark.CodeGen.ImpGen.Sequential as ImpGen
import Futhark.IR.SeqMem
import Futhark.MonadFreshNames

-- | Compile Futhark program to wasm program (some assembly
-- required).
--
-- The triple that is returned consists of
--
-- * Generated C code (to be passed to Emscripten).
--
-- * JavaScript wrapper code that presents a nicer interface to the
--   Emscripten-produced code (this should be put in a @.class.js@
--   file by itself).
--
-- * Options that should be passed to @emcc@.
compileProg :: MonadFreshNames m => T.Text -> Prog SeqMem -> m (ImpGen.Warnings, (GC.CParts, T.Text, [String]))
compileProg :: Text -> Prog SeqMem -> m (Warnings, (CParts, Text, [String]))
compileProg Text
version Prog SeqMem
prog = do
  (Warnings
ws, Program
prog') <- Prog SeqMem -> m (Warnings, Program)
forall (m :: * -> *).
MonadFreshNames m =>
Prog SeqMem -> m (Warnings, Program)
ImpGen.compileProg Prog SeqMem
prog

  CParts
prog'' <-
    Text
-> Text
-> Operations Sequential ()
-> CompilerM Sequential () ()
-> Text
-> [Space]
-> [Option]
-> Program
-> m CParts
forall (m :: * -> *) op.
MonadFreshNames m =>
Text
-> Text
-> Operations op ()
-> CompilerM op () ()
-> Text
-> [Space]
-> [Option]
-> Definitions op
-> m CParts
GC.compileProg
      Text
"wasm"
      Text
version
      Operations Sequential ()
operations
      CompilerM Sequential () ()
forall op s. CompilerM op s ()
generateBoilerplate
      Text
""
      [Space
DefaultSpace]
      []
      Program
prog'
  (Warnings, (CParts, Text, [String]))
-> m (Warnings, (CParts, Text, [String]))
forall (f :: * -> *) a. Applicative f => a -> f a
pure (Warnings
ws, (CParts
prog'', [JSEntryPoint] -> Text
javascriptWrapper (Program -> [JSEntryPoint]
fRepMyRep Program
prog'), [JSEntryPoint] -> [String]
emccExportNames (Program -> [JSEntryPoint]
fRepMyRep Program
prog')))
  where
    operations :: GC.Operations Imp.Sequential ()
    operations :: Operations Sequential ()
operations =
      Operations Sequential ()
forall op s. Operations op s
GC.defaultOperations
        { opsCompiler :: OpCompiler Sequential ()
GC.opsCompiler = CompilerM Sequential () () -> OpCompiler Sequential ()
forall a b. a -> b -> a
const (CompilerM Sequential () () -> OpCompiler Sequential ())
-> CompilerM Sequential () () -> OpCompiler Sequential ()
forall a b. (a -> b) -> a -> b
$ () -> CompilerM Sequential () ()
forall (f :: * -> *) a. Applicative f => a -> f a
pure ()
        }

fRepMyRep :: Imp.Program -> [JSEntryPoint]
fRepMyRep :: Program -> [JSEntryPoint]
fRepMyRep Program
prog =
  let Imp.Functions [(Name, Function Sequential)]
fs = Program -> Functions Sequential
forall a. Definitions a -> Functions a
Imp.defFuns Program
prog
      function :: FunctionT a -> Maybe JSEntryPoint
function (Imp.Function Maybe Name
entry [Param]
_ [Param]
_ Code a
_ [ExternalValue]
res [(Name, ExternalValue)]
args) = do
        Name
n <- Maybe Name
entry
        JSEntryPoint -> Maybe JSEntryPoint
forall a. a -> Maybe a
Just (JSEntryPoint -> Maybe JSEntryPoint)
-> JSEntryPoint -> Maybe JSEntryPoint
forall a b. (a -> b) -> a -> b
$
          JSEntryPoint :: String -> [String] -> [String] -> JSEntryPoint
JSEntryPoint
            { name :: String
name = Name -> String
nameToString Name
n,
              parameters :: [String]
parameters = ((Name, ExternalValue) -> String)
-> [(Name, ExternalValue)] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map (ExternalValue -> String
extToString (ExternalValue -> String)
-> ((Name, ExternalValue) -> ExternalValue)
-> (Name, ExternalValue)
-> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Name, ExternalValue) -> ExternalValue
forall a b. (a, b) -> b
snd) [(Name, ExternalValue)]
args,
              ret :: [String]
ret = (ExternalValue -> String) -> [ExternalValue] -> [String]
forall a b. (a -> b) -> [a] -> [b]
map ExternalValue -> String
extToString [ExternalValue]
res
            }
   in ((Name, Function Sequential) -> Maybe JSEntryPoint)
-> [(Name, Function Sequential)] -> [JSEntryPoint]
forall a b. (a -> Maybe b) -> [a] -> [b]
mapMaybe (Function Sequential -> Maybe JSEntryPoint
forall a. FunctionT a -> Maybe JSEntryPoint
function (Function Sequential -> Maybe JSEntryPoint)
-> ((Name, Function Sequential) -> Function Sequential)
-> (Name, Function Sequential)
-> Maybe JSEntryPoint
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Name, Function Sequential) -> Function Sequential
forall a b. (a, b) -> b
snd) [(Name, Function Sequential)]
fs