| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
GHC.Types.ForeignCall
Synopsis
- newtype ForeignCall = CCall CCallSpec
- isSafeForeignCall :: ForeignCall -> Bool
- data Safety
- playSafe :: Safety -> Bool
- playInterruptible :: Safety -> Bool
- data CExportSpec = CExportStatic SourceText CLabelString CCallConv
- type CLabelString = FastString
- isCLabelString :: CLabelString -> Bool
- pprCLabelString :: CLabelString -> SDoc
- data CCallSpec = CCallSpec CCallTarget CCallConv Safety
- data CCallTarget
- isDynamicTarget :: CCallTarget -> Bool
- data CCallConv
- defaultCCallConv :: CCallConv
- ccallConvToInt :: CCallConv -> Int
- ccallConvAttribute :: CCallConv -> SDoc
- data Header = Header SourceText FastString
- data CType = CType SourceText (Maybe Header) (SourceText, FastString)
Documentation
newtype ForeignCall Source #
Instances
| Binary ForeignCall Source # | |
| Defined in GHC.Types.ForeignCall Methods put_ :: BinHandle -> ForeignCall -> IO () Source # put :: BinHandle -> ForeignCall -> IO (Bin ForeignCall) Source # | |
| Outputable ForeignCall Source # | |
| Defined in GHC.Types.ForeignCall Methods ppr :: ForeignCall -> SDoc Source # | |
| Eq ForeignCall Source # | |
| Defined in GHC.Types.ForeignCall | |
isSafeForeignCall :: ForeignCall -> Bool Source #
Constructors
| PlaySafe | Might invoke Haskell GC, or do a call back, or switch threads, etc. So make sure things are tidy before the call. Additionally, in the threaded RTS we arrange for the external call to be executed by a separate OS thread, i.e., _concurrently_ to the execution of other Haskell threads. | 
| PlayInterruptible | Like PlaySafe, but additionally the worker thread running this foreign call may be unceremoniously killed, so it must be scheduled on an unbound thread. | 
| PlayRisky | None of the above can happen; the call will return without interacting with the runtime system at all. Specifically: 
 | 
Instances
| Data Safety Source # | |
| Defined in GHC.Types.ForeignCall Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Safety -> c Safety Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Safety Source # toConstr :: Safety -> Constr Source # dataTypeOf :: Safety -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Safety) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Safety) Source # gmapT :: (forall b. Data b => b -> b) -> Safety -> Safety Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Safety -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Safety -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Safety -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Safety -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Safety -> m Safety Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Safety -> m Safety Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Safety -> m Safety Source # | |
| Show Safety Source # | |
| Binary Safety Source # | |
| Outputable Safety Source # | |
| Eq Safety Source # | |
playInterruptible :: Safety -> Bool Source #
data CExportSpec Source #
Constructors
| CExportStatic SourceText CLabelString CCallConv | 
Instances
| Data CExportSpec Source # | |
| Defined in GHC.Types.ForeignCall Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CExportSpec -> c CExportSpec Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CExportSpec Source # toConstr :: CExportSpec -> Constr Source # dataTypeOf :: CExportSpec -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CExportSpec) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CExportSpec) Source # gmapT :: (forall b. Data b => b -> b) -> CExportSpec -> CExportSpec Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CExportSpec -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CExportSpec -> r Source # gmapQ :: (forall d. Data d => d -> u) -> CExportSpec -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> CExportSpec -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CExportSpec -> m CExportSpec Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CExportSpec -> m CExportSpec Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CExportSpec -> m CExportSpec Source # | |
| Binary CExportSpec Source # | |
| Defined in GHC.Types.ForeignCall Methods put_ :: BinHandle -> CExportSpec -> IO () Source # put :: BinHandle -> CExportSpec -> IO (Bin CExportSpec) Source # | |
| Outputable CExportSpec Source # | |
| Defined in GHC.Types.ForeignCall Methods ppr :: CExportSpec -> SDoc Source # | |
type CLabelString = FastString Source #
isCLabelString :: CLabelString -> Bool Source #
pprCLabelString :: CLabelString -> SDoc Source #
Constructors
| CCallSpec CCallTarget CCallConv Safety | 
data CCallTarget Source #
How to call a particular function in C-land.
Constructors
| StaticTarget SourceText CLabelString (Maybe Unit) Bool | |
| DynamicTarget | 
Instances
| Data CCallTarget Source # | |
| Defined in GHC.Types.ForeignCall Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CCallTarget -> c CCallTarget Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CCallTarget Source # toConstr :: CCallTarget -> Constr Source # dataTypeOf :: CCallTarget -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CCallTarget) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CCallTarget) Source # gmapT :: (forall b. Data b => b -> b) -> CCallTarget -> CCallTarget Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CCallTarget -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CCallTarget -> r Source # gmapQ :: (forall d. Data d => d -> u) -> CCallTarget -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> CCallTarget -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CCallTarget -> m CCallTarget Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CCallTarget -> m CCallTarget Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CCallTarget -> m CCallTarget Source # | |
| Binary CCallTarget Source # | |
| Defined in GHC.Types.ForeignCall Methods put_ :: BinHandle -> CCallTarget -> IO () Source # put :: BinHandle -> CCallTarget -> IO (Bin CCallTarget) Source # | |
| Eq CCallTarget Source # | |
| Defined in GHC.Types.ForeignCall | |
isDynamicTarget :: CCallTarget -> Bool Source #
Constructors
| CCallConv | |
| CApiConv | |
| StdCallConv | |
| PrimCallConv | |
| JavaScriptCallConv | 
Instances
| Data CCallConv Source # | |
| Defined in GHC.Types.ForeignCall Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CCallConv -> c CCallConv Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CCallConv Source # toConstr :: CCallConv -> Constr Source # dataTypeOf :: CCallConv -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CCallConv) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CCallConv) Source # gmapT :: (forall b. Data b => b -> b) -> CCallConv -> CCallConv Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CCallConv -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CCallConv -> r Source # gmapQ :: (forall d. Data d => d -> u) -> CCallConv -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> CCallConv -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CCallConv -> m CCallConv Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CCallConv -> m CCallConv Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CCallConv -> m CCallConv Source # | |
| Binary CCallConv Source # | |
| Outputable CCallConv Source # | |
| Eq CCallConv Source # | |
ccallConvToInt :: CCallConv -> Int Source #
ccallConvAttribute :: CCallConv -> SDoc Source #
Constructors
| Header SourceText FastString | 
Instances
| Data Header Source # | |
| Defined in GHC.Types.ForeignCall Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Header -> c Header Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Header Source # toConstr :: Header -> Constr Source # dataTypeOf :: Header -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Header) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Header) Source # gmapT :: (forall b. Data b => b -> b) -> Header -> Header Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Header -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Header -> r Source # gmapQ :: (forall d. Data d => d -> u) -> Header -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> Header -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Header -> m Header Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Header -> m Header Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Header -> m Header Source # | |
| Binary Header Source # | |
| Outputable Header Source # | |
| Eq Header Source # | |
A C type, used in CAPI FFI calls
- AnnKeywordId:- AnnOpen- '{-# CTYPE',- AnnHeader,- AnnVal,- AnnClose- '#-}',
Constructors
| CType SourceText (Maybe Header) (SourceText, FastString) | 
Instances
| Data CType Source # | |
| Defined in GHC.Types.ForeignCall Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CType -> c CType Source # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CType Source # toConstr :: CType -> Constr Source # dataTypeOf :: CType -> DataType Source # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CType) Source # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CType) Source # gmapT :: (forall b. Data b => b -> b) -> CType -> CType Source # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CType -> r Source # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CType -> r Source # gmapQ :: (forall d. Data d => d -> u) -> CType -> [u] Source # gmapQi :: Int -> (forall d. Data d => d -> u) -> CType -> u Source # gmapM :: Monad m => (forall d. Data d => d -> m d) -> CType -> m CType Source # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CType -> m CType Source # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CType -> m CType Source # | |
| Binary CType Source # | |
| Outputable CType Source # | |
| Eq CType Source # | |
| type Anno CType Source # | |
| Defined in GHC.Hs.Decls | |