FFI: Define ForeignSrc when FFI disabled

This commit is contained in:
Bretton 2022-08-10 01:13:20 -07:00
parent 6cc5cec191
commit 33fd5c235a
2 changed files with 29 additions and 7 deletions

View File

@ -1,5 +1,7 @@
{-# LANGUAGE BlockArguments #-}
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE RecordWildCards #-}
@ -9,24 +11,27 @@
-- | The implementation of loading and calling external functions from shared
-- libraries. Currently works on Unix only.
module Cryptol.Backend.FFI
#ifdef FFI_ENABLED
( ForeignSrc
, loadForeignSrc
, unloadForeignSrc
#ifdef FFI_ENABLED
, ForeignImpl
, loadForeignImpl
, FFIArg
, FFIRet
, SomeFFIArg (..)
, callForeignImpl
)
#endif
)
where
import Control.DeepSeq
import Cryptol.Backend.FFI.Error
#ifdef FFI_ENABLED
import Control.Concurrent.MVar
import Control.DeepSeq
import Control.Exception
import Control.Monad
import Data.Bifunctor
@ -39,9 +44,16 @@ import System.FilePath ((-<.>))
import System.IO.Error
import System.Posix.DynamicLinker
import Cryptol.Backend.FFI.Error
import Cryptol.Utils.Panic
#else
import GHC.Generics
#endif
#ifdef FFI_ENABLED
-- | A source from which we can retrieve implementations of foreign functions.
data ForeignSrc = ForeignSrc
{ -- | The 'ForeignPtr' wraps the pointer returned by 'dlopen', where the
@ -200,4 +212,14 @@ callForeignImpl ForeignImpl {..} xs = withForeignSrc foreignImplSrc \_ ->
callFFI foreignImplFun (ffiRet @a) $ map toArg xs
where toArg (SomeFFIArg x) = ffiArg x
#else
data ForeignSrc = ForeignSrc deriving (Show, Generic, NFData)
loadForeignSrc :: FilePath -> IO (Either FFILoadError ForeignSrc)
loadForeignSrc _ = pure $ Right ForeignSrc
unloadForeignSrc :: ForeignSrc -> IO ()
unloadForeignSrc _ = pure ()
#endif

View File

@ -15,6 +15,7 @@ module Cryptol.Eval.FFI
( evalForeignDecls
) where
import Cryptol.Backend.FFI
import Cryptol.Backend.FFI.Error
import Cryptol.Eval
import Cryptol.ModuleSystem.Env
@ -36,7 +37,6 @@ import LibBF (bfFromDouble, bfToDouble,
import System.Directory
import Cryptol.Backend.Concrete
import Cryptol.Backend.FFI
import Cryptol.Backend.FloatHelpers
import Cryptol.Backend.Monad
import Cryptol.Backend.SeqMap
@ -276,7 +276,7 @@ withWordType FFIWord64 f = f $ Proxy @Word64
-- | Dummy implementation for when FFI is disabled. Does not add anything to
-- the environment.
evalForeignDecls :: ModulePath -> Module -> EvalEnv ->
Eval (Either [FFILoadError] EvalEnv)
evalForeignDecls _ _ env = pure $ Right env
Eval (Either [FFILoadError] (ForeignSrc, EvalEnv))
evalForeignDecls _ _ _ = pure $ Left []
#endif