Safe Haskell | None |
---|---|
Language | Haskell2010 |
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 PrimRep [PrimRep]
- 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
Eq ForeignCall # | |
Defined in ForeignCall (==) :: ForeignCall -> ForeignCall -> Bool # (/=) :: ForeignCall -> ForeignCall -> Bool # | |
Outputable ForeignCall # | |
Defined in ForeignCall | |
Binary ForeignCall # | |
Defined in ForeignCall put_ :: BinHandle -> ForeignCall -> IO () Source # put :: BinHandle -> ForeignCall -> IO (Bin ForeignCall) Source # |
isSafeForeignCall :: ForeignCall -> Bool Source #
Instances
Eq Safety # | |
Data Safety # | |
Defined in ForeignCall 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 # | |
Outputable Safety # | |
Binary Safety # | |
playInterruptible :: Safety -> Bool Source #
data CExportSpec Source #
Instances
Data CExportSpec # | |
Defined in ForeignCall 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 # | |
Outputable CExportSpec # | |
Defined in ForeignCall | |
Binary CExportSpec # | |
Defined in ForeignCall put_ :: BinHandle -> CExportSpec -> IO () Source # put :: BinHandle -> CExportSpec -> IO (Bin CExportSpec) Source # |
type CLabelString = FastString Source #
isCLabelString :: CLabelString -> Bool Source #
pprCLabelString :: CLabelString -> SDoc Source #
data CCallTarget Source #
How to call a particular function in C-land.
Instances
Eq CCallTarget # | |
Defined in ForeignCall (==) :: CCallTarget -> CCallTarget -> Bool # (/=) :: CCallTarget -> CCallTarget -> Bool # | |
Data CCallTarget # | |
Defined in ForeignCall 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 # | |
Defined in ForeignCall put_ :: BinHandle -> CCallTarget -> IO () Source # put :: BinHandle -> CCallTarget -> IO (Bin CCallTarget) Source # |
isDynamicTarget :: CCallTarget -> Bool Source #
Instances
Eq CCallConv # | |
Data CCallConv # | |
Defined in ForeignCall 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 # | |
Outputable CCallConv # | |
Binary CCallConv # | |
ccallConvToInt :: CCallConv -> Int Source #
ccallConvAttribute :: CCallConv -> SDoc Source #
Instances
Eq Header # | |
Data Header # | |
Defined in ForeignCall 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 # | |
Outputable Header # | |
Binary Header # | |
A C type, used in CAPI FFI calls
AnnKeywordId
:AnnOpen
'{-# CTYPE'
,AnnHeader
,AnnVal
,AnnClose
'#-}'
,
Instances
Eq CType # | |
Data CType # | |
Defined in ForeignCall 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 # | |
Outputable CType # | |
Binary CType # | |