module Data.GI.GIR.BasicTypes
( Name(..)
, Transfer(..)
, Alias(..)
, Type(..)
, BasicType(..)
) where
import Data.Text (Text)
data Name = Name { Name -> Text
namespace :: Text, Name -> Text
name :: Text }
deriving (Name -> Name -> Bool
(Name -> Name -> Bool) -> (Name -> Name -> Bool) -> Eq Name
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Name -> Name -> Bool
$c/= :: Name -> Name -> Bool
== :: Name -> Name -> Bool
$c== :: Name -> Name -> Bool
Eq, Eq Name
Eq Name =>
(Name -> Name -> Ordering)
-> (Name -> Name -> Bool)
-> (Name -> Name -> Bool)
-> (Name -> Name -> Bool)
-> (Name -> Name -> Bool)
-> (Name -> Name -> Name)
-> (Name -> Name -> Name)
-> Ord Name
Name -> Name -> Bool
Name -> Name -> Ordering
Name -> Name -> Name
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Name -> Name -> Name
$cmin :: Name -> Name -> Name
max :: Name -> Name -> Name
$cmax :: Name -> Name -> Name
>= :: Name -> Name -> Bool
$c>= :: Name -> Name -> Bool
> :: Name -> Name -> Bool
$c> :: Name -> Name -> Bool
<= :: Name -> Name -> Bool
$c<= :: Name -> Name -> Bool
< :: Name -> Name -> Bool
$c< :: Name -> Name -> Bool
compare :: Name -> Name -> Ordering
$ccompare :: Name -> Name -> Ordering
$cp1Ord :: Eq Name
Ord, Int -> Name -> ShowS
[Name] -> ShowS
Name -> String
(Int -> Name -> ShowS)
-> (Name -> String) -> ([Name] -> ShowS) -> Show Name
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Name] -> ShowS
$cshowList :: [Name] -> ShowS
show :: Name -> String
$cshow :: Name -> String
showsPrec :: Int -> Name -> ShowS
$cshowsPrec :: Int -> Name -> ShowS
Show)
data Transfer = TransferNothing
| TransferContainer
| TransferEverything
deriving (Int -> Transfer -> ShowS
[Transfer] -> ShowS
Transfer -> String
(Int -> Transfer -> ShowS)
-> (Transfer -> String) -> ([Transfer] -> ShowS) -> Show Transfer
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Transfer] -> ShowS
$cshowList :: [Transfer] -> ShowS
show :: Transfer -> String
$cshow :: Transfer -> String
showsPrec :: Int -> Transfer -> ShowS
$cshowsPrec :: Int -> Transfer -> ShowS
Show, Transfer -> Transfer -> Bool
(Transfer -> Transfer -> Bool)
-> (Transfer -> Transfer -> Bool) -> Eq Transfer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Transfer -> Transfer -> Bool
$c/= :: Transfer -> Transfer -> Bool
== :: Transfer -> Transfer -> Bool
$c== :: Transfer -> Transfer -> Bool
Eq, Eq Transfer
Eq Transfer =>
(Transfer -> Transfer -> Ordering)
-> (Transfer -> Transfer -> Bool)
-> (Transfer -> Transfer -> Bool)
-> (Transfer -> Transfer -> Bool)
-> (Transfer -> Transfer -> Bool)
-> (Transfer -> Transfer -> Transfer)
-> (Transfer -> Transfer -> Transfer)
-> Ord Transfer
Transfer -> Transfer -> Bool
Transfer -> Transfer -> Ordering
Transfer -> Transfer -> Transfer
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Transfer -> Transfer -> Transfer
$cmin :: Transfer -> Transfer -> Transfer
max :: Transfer -> Transfer -> Transfer
$cmax :: Transfer -> Transfer -> Transfer
>= :: Transfer -> Transfer -> Bool
$c>= :: Transfer -> Transfer -> Bool
> :: Transfer -> Transfer -> Bool
$c> :: Transfer -> Transfer -> Bool
<= :: Transfer -> Transfer -> Bool
$c<= :: Transfer -> Transfer -> Bool
< :: Transfer -> Transfer -> Bool
$c< :: Transfer -> Transfer -> Bool
compare :: Transfer -> Transfer -> Ordering
$ccompare :: Transfer -> Transfer -> Ordering
$cp1Ord :: Eq Transfer
Ord)
newtype Alias = Alias Name deriving (Eq Alias
Eq Alias =>
(Alias -> Alias -> Ordering)
-> (Alias -> Alias -> Bool)
-> (Alias -> Alias -> Bool)
-> (Alias -> Alias -> Bool)
-> (Alias -> Alias -> Bool)
-> (Alias -> Alias -> Alias)
-> (Alias -> Alias -> Alias)
-> Ord Alias
Alias -> Alias -> Bool
Alias -> Alias -> Ordering
Alias -> Alias -> Alias
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Alias -> Alias -> Alias
$cmin :: Alias -> Alias -> Alias
max :: Alias -> Alias -> Alias
$cmax :: Alias -> Alias -> Alias
>= :: Alias -> Alias -> Bool
$c>= :: Alias -> Alias -> Bool
> :: Alias -> Alias -> Bool
$c> :: Alias -> Alias -> Bool
<= :: Alias -> Alias -> Bool
$c<= :: Alias -> Alias -> Bool
< :: Alias -> Alias -> Bool
$c< :: Alias -> Alias -> Bool
compare :: Alias -> Alias -> Ordering
$ccompare :: Alias -> Alias -> Ordering
$cp1Ord :: Eq Alias
Ord, Alias -> Alias -> Bool
(Alias -> Alias -> Bool) -> (Alias -> Alias -> Bool) -> Eq Alias
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Alias -> Alias -> Bool
$c/= :: Alias -> Alias -> Bool
== :: Alias -> Alias -> Bool
$c== :: Alias -> Alias -> Bool
Eq, Int -> Alias -> ShowS
[Alias] -> ShowS
Alias -> String
(Int -> Alias -> ShowS)
-> (Alias -> String) -> ([Alias] -> ShowS) -> Show Alias
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Alias] -> ShowS
$cshowList :: [Alias] -> ShowS
show :: Alias -> String
$cshow :: Alias -> String
showsPrec :: Int -> Alias -> ShowS
$cshowsPrec :: Int -> Alias -> ShowS
Show)
data BasicType = TBoolean
| TInt
| TUInt
| TLong
| TULong
| TInt8
| TUInt8
| TInt16
| TUInt16
| TInt32
| TUInt32
| TInt64
| TUInt64
| TFloat
| TDouble
| TUniChar
| TGType
| TUTF8
| TFileName
| TPtr
| TIntPtr
| TUIntPtr
deriving (BasicType -> BasicType -> Bool
(BasicType -> BasicType -> Bool)
-> (BasicType -> BasicType -> Bool) -> Eq BasicType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: BasicType -> BasicType -> Bool
$c/= :: BasicType -> BasicType -> Bool
== :: BasicType -> BasicType -> Bool
$c== :: BasicType -> BasicType -> Bool
Eq, Int -> BasicType -> ShowS
[BasicType] -> ShowS
BasicType -> String
(Int -> BasicType -> ShowS)
-> (BasicType -> String)
-> ([BasicType] -> ShowS)
-> Show BasicType
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [BasicType] -> ShowS
$cshowList :: [BasicType] -> ShowS
show :: BasicType -> String
$cshow :: BasicType -> String
showsPrec :: Int -> BasicType -> ShowS
$cshowsPrec :: Int -> BasicType -> ShowS
Show, Eq BasicType
Eq BasicType =>
(BasicType -> BasicType -> Ordering)
-> (BasicType -> BasicType -> Bool)
-> (BasicType -> BasicType -> Bool)
-> (BasicType -> BasicType -> Bool)
-> (BasicType -> BasicType -> Bool)
-> (BasicType -> BasicType -> BasicType)
-> (BasicType -> BasicType -> BasicType)
-> Ord BasicType
BasicType -> BasicType -> Bool
BasicType -> BasicType -> Ordering
BasicType -> BasicType -> BasicType
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: BasicType -> BasicType -> BasicType
$cmin :: BasicType -> BasicType -> BasicType
max :: BasicType -> BasicType -> BasicType
$cmax :: BasicType -> BasicType -> BasicType
>= :: BasicType -> BasicType -> Bool
$c>= :: BasicType -> BasicType -> Bool
> :: BasicType -> BasicType -> Bool
$c> :: BasicType -> BasicType -> Bool
<= :: BasicType -> BasicType -> Bool
$c<= :: BasicType -> BasicType -> Bool
< :: BasicType -> BasicType -> Bool
$c< :: BasicType -> BasicType -> Bool
compare :: BasicType -> BasicType -> Ordering
$ccompare :: BasicType -> BasicType -> Ordering
$cp1Ord :: Eq BasicType
Ord)
data Type
= TBasicType BasicType
| TError
| TVariant
| TParamSpec
| TCArray Bool Int Int Type
| TGArray Type
| TPtrArray Type
| TByteArray
| TGList Type
| TGSList Type
| TGHash Type Type
| TGClosure (Maybe Type)
| TInterface Name
deriving (Type -> Type -> Bool
(Type -> Type -> Bool) -> (Type -> Type -> Bool) -> Eq Type
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Type -> Type -> Bool
$c/= :: Type -> Type -> Bool
== :: Type -> Type -> Bool
$c== :: Type -> Type -> Bool
Eq, Int -> Type -> ShowS
[Type] -> ShowS
Type -> String
(Int -> Type -> ShowS)
-> (Type -> String) -> ([Type] -> ShowS) -> Show Type
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Type] -> ShowS
$cshowList :: [Type] -> ShowS
show :: Type -> String
$cshow :: Type -> String
showsPrec :: Int -> Type -> ShowS
$cshowsPrec :: Int -> Type -> ShowS
Show, Eq Type
Eq Type =>
(Type -> Type -> Ordering)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Bool)
-> (Type -> Type -> Type)
-> (Type -> Type -> Type)
-> Ord Type
Type -> Type -> Bool
Type -> Type -> Ordering
Type -> Type -> Type
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Type -> Type -> Type
$cmin :: Type -> Type -> Type
max :: Type -> Type -> Type
$cmax :: Type -> Type -> Type
>= :: Type -> Type -> Bool
$c>= :: Type -> Type -> Bool
> :: Type -> Type -> Bool
$c> :: Type -> Type -> Bool
<= :: Type -> Type -> Bool
$c<= :: Type -> Type -> Bool
< :: Type -> Type -> Bool
$c< :: Type -> Type -> Bool
compare :: Type -> Type -> Ordering
$ccompare :: Type -> Type -> Ordering
$cp1Ord :: Eq Type
Ord)