{-# LANGUAGE DerivingVia #-}
module GHC.Types.ForeignStubs
( ForeignStubs (..)
, CHeader(..)
, CStub(..)
, appendStubC
)
where
import GHC.Utils.Outputable
import Data.Monoid
import Data.Semigroup
import Data.Coerce
newtype CStub = CStub { CStub -> SDoc
getCStub :: SDoc }
emptyCStub :: CStub
emptyCStub :: CStub
emptyCStub = SDoc -> CStub
CStub SDoc
empty
instance Monoid CStub where
mempty :: CStub
mempty = CStub
emptyCStub
mconcat :: [CStub] -> CStub
mconcat = coerce :: forall a b. Coercible a b => a -> b
coerce [SDoc] -> SDoc
vcat
instance Semigroup CStub where
<> :: CStub -> CStub -> CStub
(<>) = coerce :: forall a b. Coercible a b => a -> b
coerce SDoc -> SDoc -> SDoc
($$)
newtype = { :: SDoc }
deriving (Semigroup CHeader
CHeader
[CHeader] -> CHeader
CHeader -> CHeader -> CHeader
forall a.
Semigroup a -> a -> (a -> a -> a) -> ([a] -> a) -> Monoid a
mconcat :: [CHeader] -> CHeader
$cmconcat :: [CHeader] -> CHeader
mappend :: CHeader -> CHeader -> CHeader
$cmappend :: CHeader -> CHeader -> CHeader
mempty :: CHeader
$cmempty :: CHeader
Monoid, NonEmpty CHeader -> CHeader
CHeader -> CHeader -> CHeader
forall b. Integral b => b -> CHeader -> CHeader
forall a.
(a -> a -> a)
-> (NonEmpty a -> a)
-> (forall b. Integral b => b -> a -> a)
-> Semigroup a
stimes :: forall b. Integral b => b -> CHeader -> CHeader
$cstimes :: forall b. Integral b => b -> CHeader -> CHeader
sconcat :: NonEmpty CHeader -> CHeader
$csconcat :: NonEmpty CHeader -> CHeader
<> :: CHeader -> CHeader -> CHeader
$c<> :: CHeader -> CHeader -> CHeader
Semigroup) via CStub
data ForeignStubs
= NoStubs
| ForeignStubs CHeader CStub
appendStubC :: ForeignStubs -> CStub -> ForeignStubs
appendStubC :: ForeignStubs -> CStub -> ForeignStubs
appendStubC ForeignStubs
NoStubs CStub
c_code = CHeader -> CStub -> ForeignStubs
ForeignStubs forall a. Monoid a => a
mempty CStub
c_code
appendStubC (ForeignStubs CHeader
h CStub
c) CStub
c_code = CHeader -> CStub -> ForeignStubs
ForeignStubs CHeader
h (CStub
c forall a. Monoid a => a -> a -> a
`mappend` CStub
c_code)