-- | Basic types used in GIR parsing.
module Data.GI.GIR.BasicTypes
    ( Name(..)
    , Transfer(..)
    , Alias(..)
    , Type(..)
    , BasicType(..)
    ) where

import Data.Text (Text)

-- | Name for a symbol in the GIR file.
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
$c== :: Name -> Name -> Bool
== :: Name -> Name -> Bool
$c/= :: Name -> Name -> Bool
/= :: 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
$ccompare :: Name -> Name -> Ordering
compare :: Name -> Name -> Ordering
$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
>= :: Name -> Name -> Bool
$cmax :: Name -> Name -> Name
max :: Name -> Name -> Name
$cmin :: Name -> Name -> Name
min :: Name -> Name -> 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
$cshowsPrec :: Int -> Name -> ShowS
showsPrec :: Int -> Name -> ShowS
$cshow :: Name -> String
show :: Name -> String
$cshowList :: [Name] -> ShowS
showList :: [Name] -> ShowS
Show)

-- | Transfer mode for an argument or property.
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
$cshowsPrec :: Int -> Transfer -> ShowS
showsPrec :: Int -> Transfer -> ShowS
$cshow :: Transfer -> String
show :: Transfer -> String
$cshowList :: [Transfer] -> ShowS
showList :: [Transfer] -> ShowS
Show, Transfer -> Transfer -> Bool
(Transfer -> Transfer -> Bool)
-> (Transfer -> Transfer -> Bool) -> Eq Transfer
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Transfer -> Transfer -> Bool
== :: Transfer -> Transfer -> Bool
$c/= :: Transfer -> Transfer -> Bool
/= :: 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
$ccompare :: Transfer -> Transfer -> Ordering
compare :: Transfer -> Transfer -> Ordering
$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
>= :: Transfer -> Transfer -> Bool
$cmax :: Transfer -> Transfer -> Transfer
max :: Transfer -> Transfer -> Transfer
$cmin :: Transfer -> Transfer -> Transfer
min :: Transfer -> Transfer -> Transfer
Ord)

-- | An alias, which is simply (Namespace, name).
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
$ccompare :: Alias -> Alias -> Ordering
compare :: Alias -> Alias -> Ordering
$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
>= :: Alias -> Alias -> Bool
$cmax :: Alias -> Alias -> Alias
max :: Alias -> Alias -> Alias
$cmin :: Alias -> Alias -> Alias
min :: Alias -> Alias -> Alias
Ord, Alias -> Alias -> Bool
(Alias -> Alias -> Bool) -> (Alias -> Alias -> Bool) -> Eq Alias
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Alias -> Alias -> Bool
== :: Alias -> Alias -> Bool
$c/= :: Alias -> Alias -> Bool
/= :: 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
$cshowsPrec :: Int -> Alias -> ShowS
showsPrec :: Int -> Alias -> ShowS
$cshow :: Alias -> String
show :: Alias -> String
$cshowList :: [Alias] -> ShowS
showList :: [Alias] -> ShowS
Show)

-- | Basic types. These are generally trivial to marshal, and the GIR
-- assumes that they are defined.
data BasicType = TBoolean         -- ^ gboolean
               | TInt             -- ^ gint
               | TUInt            -- ^ guint
               | TLong            -- ^ glong
               | TULong           -- ^ gulong
               | TInt8            -- ^ gint8
               | TUInt8           -- ^ guint8
               | TInt16           -- ^ gint16
               | TUInt16          -- ^ guint16
               | TInt32           -- ^ gint32
               | TUInt32          -- ^ guint32
               | TInt64           -- ^ gint64
               | TUInt64          -- ^ guint64
               | TFloat           -- ^ gfloat
               | TDouble          -- ^ gdouble
               | TUniChar         -- ^ gunichar
               | TGType           -- ^ GType
               | TUTF8            -- ^ gchar*, encoded as UTF-8
               | TFileName        -- ^ gchar*, encoding a filename
               | TPtr             -- ^ gpointer
               | TIntPtr          -- ^ gintptr
               | TUIntPtr         -- ^ guintptr
                 deriving (BasicType -> BasicType -> Bool
(BasicType -> BasicType -> Bool)
-> (BasicType -> BasicType -> Bool) -> Eq BasicType
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: BasicType -> BasicType -> Bool
== :: BasicType -> BasicType -> Bool
$c/= :: BasicType -> BasicType -> Bool
/= :: 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
$cshowsPrec :: Int -> BasicType -> ShowS
showsPrec :: Int -> BasicType -> ShowS
$cshow :: BasicType -> String
show :: BasicType -> String
$cshowList :: [BasicType] -> ShowS
showList :: [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
$ccompare :: BasicType -> BasicType -> Ordering
compare :: BasicType -> BasicType -> Ordering
$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
>= :: BasicType -> BasicType -> Bool
$cmax :: BasicType -> BasicType -> BasicType
max :: BasicType -> BasicType -> BasicType
$cmin :: BasicType -> BasicType -> BasicType
min :: BasicType -> BasicType -> BasicType
Ord)

-- | This type represents the types found in GObject Introspection
-- interfaces: the types of constants, arguments, etc.
data Type
    = TBasicType BasicType
    | TError           -- ^ GError
    | TVariant         -- ^ GVariant
    | TGValue          -- ^ GValue
    | TParamSpec       -- ^ GParamSpec
    | TCArray Bool Int Int Type  -- ^ Zero terminated, Array Fixed
                                 -- Size, Array Length, Element Type
    | TGArray Type     -- ^ GArray
    | TPtrArray Type   -- ^ GPtrArray
    | TByteArray       -- ^ GByteArray
    | TGList Type      -- ^ GList
    | TGSList Type     -- ^ GSList
    | TGHash Type Type -- ^ GHashTable
    | TGClosure (Maybe Type) -- ^ GClosure containing the given API (if known)
    | TInterface Name  -- ^ A reference to some API in the GIR
      deriving (Type -> Type -> Bool
(Type -> Type -> Bool) -> (Type -> Type -> Bool) -> Eq Type
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
$c== :: Type -> Type -> Bool
== :: Type -> Type -> Bool
$c/= :: Type -> Type -> Bool
/= :: 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
$cshowsPrec :: Int -> Type -> ShowS
showsPrec :: Int -> Type -> ShowS
$cshow :: Type -> String
show :: Type -> String
$cshowList :: [Type] -> ShowS
showList :: [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
$ccompare :: Type -> Type -> Ordering
compare :: Type -> Type -> Ordering
$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
>= :: Type -> Type -> Bool
$cmax :: Type -> Type -> Type
max :: Type -> Type -> Type
$cmin :: Type -> Type -> Type
min :: Type -> Type -> Type
Ord)