------------------------------------------------------------------------------
-- |
-- Module:      Database.PostgreSQL.Simple.TypeInfo.Types
-- Copyright:   (c) 2013 Leon P Smith
-- License:     BSD3
-- Maintainer:  Leon P Smith <leon@melding-monads.com>
-- Stability:   experimental
--
------------------------------------------------------------------------------

module Database.PostgreSQL.Simple.TypeInfo.Types where

import Data.ByteString(ByteString)
import Database.PostgreSQL.LibPQ(Oid)
import Data.Vector(Vector)

-- | A structure representing some of the metadata regarding a PostgreSQL
--   type,  mostly taken from the @pg_type@ table.

data TypeInfo

  = Basic { TypeInfo -> Oid
typoid      :: {-# UNPACK #-} !Oid
          , TypeInfo -> Char
typcategory :: {-# UNPACK #-} !Char
          , TypeInfo -> Char
typdelim    :: {-# UNPACK #-} !Char
          , TypeInfo -> ByteString
typname     :: !ByteString
          }

  | Array { typoid      :: {-# UNPACK #-} !Oid
          , typcategory :: {-# UNPACK #-} !Char
          , typdelim    :: {-# UNPACK #-} !Char
          , typname     :: !ByteString
          , TypeInfo -> TypeInfo
typelem     :: !TypeInfo
          }

  | Range { typoid      :: {-# UNPACK #-} !Oid
          , typcategory :: {-# UNPACK #-} !Char
          , typdelim    :: {-# UNPACK #-} !Char
          , typname     :: !ByteString
          , TypeInfo -> TypeInfo
rngsubtype  :: !TypeInfo
          }

  | Composite { typoid      :: {-# UNPACK #-} !Oid
              , typcategory :: {-# UNPACK #-} !Char
              , typdelim    :: {-# UNPACK #-} !Char
              , typname     :: !ByteString
              , TypeInfo -> Oid
typrelid    :: {-# UNPACK #-} !Oid
              , TypeInfo -> Vector Attribute
attributes  :: !(Vector Attribute)
              }

    deriving (Int -> TypeInfo -> ShowS
[TypeInfo] -> ShowS
TypeInfo -> String
(Int -> TypeInfo -> ShowS)
-> (TypeInfo -> String) -> ([TypeInfo] -> ShowS) -> Show TypeInfo
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [TypeInfo] -> ShowS
$cshowList :: [TypeInfo] -> ShowS
show :: TypeInfo -> String
$cshow :: TypeInfo -> String
showsPrec :: Int -> TypeInfo -> ShowS
$cshowsPrec :: Int -> TypeInfo -> ShowS
Show)

data Attribute
   = Attribute { Attribute -> ByteString
attname :: !ByteString
               , Attribute -> TypeInfo
atttype :: !TypeInfo
               }
     deriving (Int -> Attribute -> ShowS
[Attribute] -> ShowS
Attribute -> String
(Int -> Attribute -> ShowS)
-> (Attribute -> String)
-> ([Attribute] -> ShowS)
-> Show Attribute
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Attribute] -> ShowS
$cshowList :: [Attribute] -> ShowS
show :: Attribute -> String
$cshow :: Attribute -> String
showsPrec :: Int -> Attribute -> ShowS
$cshowsPrec :: Int -> Attribute -> ShowS
Show)