{-# LANGUAGE ImportQualifiedPost #-}
{-# LANGUAGE OverloadedStrings   #-}

module Dovetail.FFI 
  ( 
  -- * Foreign function interface
    FFI(..)
  , ForeignImport(..)
  , toEnv
  , toExterns
  ) where

import Data.Map qualified as Map  
import Dovetail.Types 
import Language.PureScript qualified as P
import Language.PureScript.Externs qualified as Externs
  
-- | Describes a module which is implemented in Haskell, and made available
-- to PureScript code using its foreign function interface. 
--
-- Right now, this consists only of foreign value declarations, even though
-- the FFI supports other forms of interop.
--
-- Values of this type can be constructed directly, but in many cases it is
-- simpler to use the "Dovetail.FFI.Builder" module
-- instead.
--
-- Values of this type can be consumed by the 'toExterns' and 'toEnv' functions,
-- and their results passed to the PureScript APIs or the low-level functions in
-- "Dovetail.Evaluate" and "Dovetail.Build", 
-- directly, but it is more likely that you will use values of this type with the 
-- higher-level 'Dovetail.ffi' function.
data FFI ctx = FFI
  { FFI ctx -> ModuleName
ffi_moduleName :: P.ModuleName
  -- ^ The module name for the module being implemented in Haskell.
  , FFI ctx -> [ForeignImport ctx]
ffi_values :: [ForeignImport ctx]
  -- ^ A list of values implemented in Haskell in this module.
  }
  
-- | A single value implemented in a foreign Haskell module.
data ForeignImport ctx = ForeignImport
  { ForeignImport ctx -> Ident
fv_name :: P.Ident
  -- ^ The name of this value in PureScript code
  , ForeignImport ctx -> SourceType
fv_type :: P.SourceType
  -- ^ The PureScript type of this value
  , ForeignImport ctx -> Value ctx
fv_value :: Value ctx
  -- ^ The value itself
  }

-- | Convert a foreign module into a PureScript externs file, for use during
-- separate compilation.
--
-- For advanced use cases, the result may be used with the functions in the 
-- "Dovetail.Build" module.
toExterns :: FFI ctx -> P.ExternsFile
toExterns :: FFI ctx -> ExternsFile
toExterns (FFI ModuleName
mn [ForeignImport ctx]
vals) =
  ExternsFile :: Text
-> ModuleName
-> [DeclarationRef]
-> [ExternsImport]
-> [ExternsFixity]
-> [ExternsTypeFixity]
-> [ExternsDeclaration]
-> SourceSpan
-> ExternsFile
Externs.ExternsFile   
    { efVersion :: Text
Externs.efVersion      = Text
"0.14.2"
    , efModuleName :: ModuleName
Externs.efModuleName   = ModuleName
mn
    , efExports :: [DeclarationRef]
Externs.efExports      = [SourceSpan -> Ident -> DeclarationRef
P.ValueRef SourceSpan
P.nullSourceSpan Ident
name | ForeignImport Ident
name SourceType
_ Value ctx
_ <- [ForeignImport ctx]
vals]
    , efImports :: [ExternsImport]
Externs.efImports      = [ ModuleName
-> ImportDeclarationType -> Maybe ModuleName -> ExternsImport
P.ExternsImport (Text -> ModuleName
P.ModuleName Text
"Prim") ImportDeclarationType
P.Implicit (ModuleName -> Maybe ModuleName
forall a. a -> Maybe a
Just (Text -> ModuleName
P.ModuleName Text
"Prim"))
                               , ModuleName
-> ImportDeclarationType -> Maybe ModuleName -> ExternsImport
P.ExternsImport (Text -> ModuleName
P.ModuleName Text
"Prim") ImportDeclarationType
P.Implicit Maybe ModuleName
forall a. Maybe a
Nothing
                               ]
    , efFixities :: [ExternsFixity]
Externs.efFixities     = []
    , efTypeFixities :: [ExternsTypeFixity]
Externs.efTypeFixities = []
    , efDeclarations :: [ExternsDeclaration]
Externs.efDeclarations = [Ident -> SourceType -> ExternsDeclaration
Externs.EDValue Ident
name SourceType
ty | ForeignImport Ident
name SourceType
ty Value ctx
_ <- [ForeignImport ctx]
vals]
    , efSourceSpan :: SourceSpan
Externs.efSourceSpan   = SourceSpan
P.nullSourceSpan
    } 

-- | Convert a foreign module into an evaluation environment.
--
-- For advanced use cases, the result may be used with the functions in the 
-- "Dovetail.Evaluate" module.
toEnv :: FFI ctx -> Env ctx
toEnv :: FFI ctx -> Env ctx
toEnv (FFI ModuleName
mn [ForeignImport ctx]
vals) = 
  Map (Qualified Ident) (Value ctx) -> Env ctx
forall ctx. Map (Qualified Ident) (Value ctx) -> Env ctx
envFromMap (Map (Qualified Ident) (Value ctx) -> Env ctx)
-> Map (Qualified Ident) (Value ctx) -> Env ctx
forall a b. (a -> b) -> a -> b
$ [(Qualified Ident, Value ctx)] -> Map (Qualified Ident) (Value ctx)
forall k a. Ord k => [(k, a)] -> Map k a
Map.fromList [ (Ident -> ModuleName -> Qualified Ident
forall a. a -> ModuleName -> Qualified a
P.mkQualified Ident
name ModuleName
mn, Value ctx
val) | ForeignImport Ident
name SourceType
_ Value ctx
val <- [ForeignImport ctx]
vals ]