module Data.GI.CodeGen.Constant
( genConstant
) where
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative ((<$>))
#endif
import Data.Monoid ((<>))
import Data.Text (Text)
import Data.GI.CodeGen.API
import Data.GI.CodeGen.Code
import Data.GI.CodeGen.Conversions
import Data.GI.CodeGen.Haddock (deprecatedPragma, writeDocumentation,
RelativeDocPosition(..))
import Data.GI.CodeGen.Type
import Data.GI.CodeGen.Util (tshow)
data PatternSynonym = SimpleSynonym PSValue PSType
| ExplicitSynonym PSView PSExpression PSValue PSType
type PSValue = Text
type PSType = Text
type PSView = Text
type PSExpression = Text
writePattern :: Text -> PatternSynonym -> CodeGen ()
writePattern name (SimpleSynonym value t) = line $
"pattern " <> name <> " = " <> value <> " :: " <> t
writePattern name (ExplicitSynonym view expression value t) = do
setModuleMinBase Base48
line $ "pattern " <> name <> " <- (" <> view <> " -> "
<> value <> ") :: " <> t <> " where"
indent $ line $
name <> " = " <> expression <> " " <> value <> " :: " <> t
genConstant :: Name -> Constant -> CodeGen ()
genConstant (Name _ name) c = group $ do
setLanguagePragmas ["PatternSynonyms", "ScopedTypeVariables", "ViewPatterns"]
deprecatedPragma name (constantDeprecated c)
handleCGExc (\e -> line $ "-- XXX: Could not generate constant: " <> describeCGError e)
(do writeDocumentation DocBeforeSymbol (constantDocumentation c)
assignValue name (constantType c) (constantValue c)
export ToplevelSection ("pattern " <> name))
assignValue :: Text -> Type -> Text -> ExcCodeGen ()
assignValue name t@(TBasicType TPtr) value = do
ht <- typeShow <$> haskellType t
writePattern name (ExplicitSynonym "ptrToIntPtr" "intPtrToPtr" value ht)
assignValue name t@(TBasicType b) value = do
ht <- typeShow <$> haskellType t
hv <- showBasicType b value
writePattern name (SimpleSynonym hv ht)
assignValue name t@(TInterface _) value = do
ht <- typeShow <$> haskellType t
api <- findAPI t
case api of
Just (APIEnum _) ->
writePattern name (ExplicitSynonym "fromEnum" "toEnum" value ht)
Just (APIFlags _) -> do
let wordValue = "(" <> value <> " :: Word64)"
writePattern name (ExplicitSynonym "gflagsToWord" "wordToGFlags" wordValue ht)
_ -> notImplementedError $ "Don't know how to treat constants of type " <> tshow t
assignValue _ t _ = notImplementedError $ "Don't know how to treat constants of type " <> tshow t
showBasicType :: BasicType -> Text -> ExcCodeGen Text
showBasicType TInt i = return i
showBasicType TUInt i = return i
showBasicType TLong i = return i
showBasicType TULong i = return i
showBasicType TInt8 i = return i
showBasicType TUInt8 i = return i
showBasicType TInt16 i = return i
showBasicType TUInt16 i = return i
showBasicType TInt32 i = return i
showBasicType TUInt32 i = return i
showBasicType TInt64 i = return i
showBasicType TUInt64 i = return i
showBasicType TBoolean "0" = return "False"
showBasicType TBoolean "false" = return "False"
showBasicType TBoolean "1" = return "True"
showBasicType TBoolean "true" = return "True"
showBasicType TBoolean b = notImplementedError $ "Could not parse boolean \"" <> b <> "\""
showBasicType TFloat f = return f
showBasicType TDouble d = return d
showBasicType TUTF8 s = return . tshow $ s
showBasicType TFileName fn = return . tshow $ fn
showBasicType TUniChar c = return $ "'" <> c <> "'"
showBasicType TGType gtype = return $ "GType " <> gtype
showBasicType TIntPtr ptr = return ptr
showBasicType TUIntPtr ptr = return ptr
showBasicType TPtr _ = notImplementedError $ "Cannot directly show a pointer"