Skip to content

Commit

Permalink
Merge branch 'master' into shellnix
Browse files Browse the repository at this point in the history
  • Loading branch information
wavewave committed Jun 24, 2018
2 parents d0e7d12 + c75ce1b commit b04507c
Showing 1 changed file with 14 additions and 0 deletions.
14 changes: 14 additions & 0 deletions fficxx/lib/FFICXX/Generate/Util/HaskellSrcExts.hs
Original file line number Diff line number Diff line change
@@ -1,3 +1,4 @@
{-# LANGUAGE CPP #-}
-----------------------------------------------------------------------------
-- |
-- Module : FFICXX.Generate.Util.HaskellSrcExts
Expand All @@ -14,6 +15,7 @@
module FFICXX.Generate.Util.HaskellSrcExts where

import Data.List (foldl')
import Data.Maybe
import Language.Haskell.Exts hiding (unit_tycon)
import qualified Language.Haskell.Exts (unit_tycon)

Expand Down Expand Up @@ -106,11 +108,19 @@ mkInstance ctxt n typs idecls = InstDecl () Nothing instrule (Just idecls)
where f acc x = IHApp () acc (tyParen x)

mkData :: String -> [TyVarBind ()] -> [QualConDecl ()] -> Maybe (Deriving ()) -> Decl ()
#if MIN_VERSION_haskell_src_exts(1,20,0)
mkData n tbinds qdecls mderiv = DataDecl () (DataType ()) Nothing declhead qdecls (maybeToList mderiv)
#else
mkData n tbinds qdecls mderiv = DataDecl () (DataType ()) Nothing declhead qdecls mderiv
#endif
where declhead = mkDeclHead n tbinds

mkNewtype :: String -> [TyVarBind ()] -> [QualConDecl ()] -> Maybe (Deriving ()) -> Decl ()
#if MIN_VERSION_haskell_src_exts(1,20,0)
mkNewtype n tbinds qdecls mderiv = DataDecl () (NewType ()) Nothing declhead qdecls (maybeToList mderiv)
#else
mkNewtype n tbinds qdecls mderiv = DataDecl () (NewType ()) Nothing declhead qdecls mderiv
#endif
where declhead = mkDeclHead n tbinds

mkForImpCcall :: String -> String -> Type () -> Decl ()
Expand Down Expand Up @@ -172,7 +182,11 @@ bracketExp = BracketExp ()
typeBracket = TypeBracket ()


#if MIN_VERSION_haskell_src_exts(1,20,0)
mkDeriving = Deriving () Nothing
#else
mkDeriving = Deriving ()
#endif

irule = IRule ()

Expand Down

0 comments on commit b04507c

Please sign in to comment.