module Data.GI.CodeGen.Type
( Type(..)
, BasicType(..)
, TypeRep
, con
, con0
, typeShow
, typeConName
, io
, ptr
, funptr
, maybeT
) where
#if !MIN_VERSION_base(4,11,0)
import Data.Monoid ((<>))
#endif
import qualified Data.Text as T
import Data.Text (Text)
import Data.GI.GIR.BasicTypes (Type(..), BasicType(..))
data TypeRep = TypeRep { TypeRep -> TypeCon
typeCon :: TypeCon
, TypeRep -> [TypeRep]
typeConArgs :: [TypeRep]
} deriving (TypeRep -> TypeRep -> Bool
(TypeRep -> TypeRep -> Bool)
-> (TypeRep -> TypeRep -> Bool) -> Eq TypeRep
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TypeRep -> TypeRep -> Bool
== :: TypeRep -> TypeRep -> Bool
$c/= :: TypeRep -> TypeRep -> Bool
/= :: TypeRep -> TypeRep -> Bool
Eq)
data TypeCon = TupleCon
| ListCon
| TextualCon Text
deriving (TypeCon -> TypeCon -> Bool
(TypeCon -> TypeCon -> Bool)
-> (TypeCon -> TypeCon -> Bool) -> Eq TypeCon
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: TypeCon -> TypeCon -> Bool
== :: TypeCon -> TypeCon -> Bool
$c/= :: TypeCon -> TypeCon -> Bool
/= :: TypeCon -> TypeCon -> Bool
Eq)
typeShow :: TypeRep -> Text
typeShow :: TypeRep -> Text
typeShow (TypeRep TypeCon
TupleCon [TypeRep]
args) =
Text
"(" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> [Text] -> Text
T.intercalate Text
", " ((TypeRep -> Text) -> [TypeRep] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map TypeRep -> Text
typeShow [TypeRep]
args) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")"
typeShow (TypeRep TypeCon
ListCon [TypeRep]
args) =
Text
"[" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text -> [Text] -> Text
T.intercalate Text
", " ((TypeRep -> Text) -> [TypeRep] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map TypeRep -> Text
typeShow [TypeRep]
args) Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"]"
typeShow (TypeRep (TextualCon Text
con) [TypeRep]
args) =
Text -> [Text] -> Text
T.intercalate Text
" " (Text
con Text -> [Text] -> [Text]
forall a. a -> [a] -> [a]
: (TypeRep -> Text) -> [TypeRep] -> [Text]
forall a b. (a -> b) -> [a] -> [b]
map (Text -> Text
parenthesize (Text -> Text) -> (TypeRep -> Text) -> TypeRep -> Text
forall b c a. (b -> c) -> (a -> b) -> a -> c
. TypeRep -> Text
typeShow) [TypeRep]
args)
where parenthesize :: Text -> Text
parenthesize :: Text -> Text
parenthesize Text
s = if (Char -> Bool) -> Text -> Bool
T.any (Char -> Char -> Bool
forall a. Eq a => a -> a -> Bool
== Char
' ') Text
s
then Text
"(" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
s Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
")"
else Text
s
typeConName :: TypeRep -> Text
typeConName :: TypeRep -> Text
typeConName (TypeRep TypeCon
TupleCon [TypeRep]
_) = Text
"(,)"
typeConName (TypeRep TypeCon
ListCon [TypeRep]
_) = Text
"[,]"
typeConName (TypeRep (TextualCon Text
s) [TypeRep]
_) = Text
s
con :: Text -> [TypeRep] -> TypeRep
con :: Text -> [TypeRep] -> TypeRep
con Text
"[]" [TypeRep]
xs = TypeRep {typeCon :: TypeCon
typeCon = TypeCon
ListCon, typeConArgs :: [TypeRep]
typeConArgs = [TypeRep]
xs }
con Text
"(,)" [TypeRep]
xs = TypeRep {typeCon :: TypeCon
typeCon = TypeCon
TupleCon, typeConArgs :: [TypeRep]
typeConArgs = [TypeRep]
xs }
con Text
s [TypeRep]
xs = TypeRep {typeCon :: TypeCon
typeCon = Text -> TypeCon
TextualCon Text
s, typeConArgs :: [TypeRep]
typeConArgs = [TypeRep]
xs}
con0 :: Text -> TypeRep
con0 :: Text -> TypeRep
con0 Text
c = Text -> [TypeRep] -> TypeRep
con Text
c []
io :: TypeRep -> TypeRep
io :: TypeRep -> TypeRep
io TypeRep
t = Text
"IO" Text -> [TypeRep] -> TypeRep
`con` [TypeRep
t]
ptr :: TypeRep -> TypeRep
ptr :: TypeRep -> TypeRep
ptr TypeRep
t = Text
"Ptr" Text -> [TypeRep] -> TypeRep
`con` [TypeRep
t]
funptr :: TypeRep -> TypeRep
funptr :: TypeRep -> TypeRep
funptr TypeRep
t = Text
"FunPtr" Text -> [TypeRep] -> TypeRep
`con` [TypeRep
t]
maybeT :: TypeRep -> TypeRep
maybeT :: TypeRep -> TypeRep
maybeT TypeRep
t = Text
"Maybe" Text -> [TypeRep] -> TypeRep
`con` [TypeRep
t]