never executed always true always false
    1 -- | Foreign export stubs
    2 {-# LANGUAGE DerivingVia #-}
    3 module GHC.Types.ForeignStubs
    4    ( ForeignStubs (..)
    5    , CHeader(..)
    6    , CStub(..)
    7    , appendStubC
    8    )
    9 where
   10 
   11 import GHC.Utils.Outputable
   12 import Data.Monoid
   13 import Data.Semigroup
   14 import Data.Coerce
   15 
   16 newtype CStub = CStub { getCStub :: SDoc }
   17 
   18 emptyCStub :: CStub
   19 emptyCStub = CStub empty
   20 
   21 instance Monoid CStub where
   22   mempty = emptyCStub
   23   mconcat = coerce vcat
   24 
   25 instance Semigroup CStub where
   26   (<>) = coerce ($$)
   27 
   28 newtype CHeader = CHeader { getCHeader :: SDoc }
   29   deriving (Monoid, Semigroup) via CStub
   30 
   31 -- | Foreign export stubs
   32 data ForeignStubs
   33   = NoStubs
   34       -- ^ We don't have any stubs
   35   | ForeignStubs CHeader CStub
   36       -- ^ There are some stubs. Parameters:
   37       --
   38       --  1) Header file prototypes for
   39       --     "foreign exported" functions
   40       --
   41       --  2) C stubs to use when calling
   42       --     "foreign exported" functions
   43 
   44 appendStubC :: ForeignStubs -> CStub -> ForeignStubs
   45 appendStubC NoStubs         c_code = ForeignStubs mempty c_code
   46 appendStubC (ForeignStubs h c) c_code = ForeignStubs h (c `mappend` c_code)