module Database.PostgreSQL.Simple.TypeInfo.Types where
import Data.ByteString(ByteString)
import Database.PostgreSQL.LibPQ(Oid)
import Data.Vector(Vector)
data TypeInfo
  = Basic { typoid      ::  !Oid
          , typcategory ::  !Char
          , typdelim    ::  !Char
          , typname     :: !ByteString
          }
  | Array { typoid      ::  !Oid
          , typcategory ::  !Char
          , typdelim    ::  !Char
          , typname     :: !ByteString
          , typelem     :: !TypeInfo
          }
  | Range { typoid      ::  !Oid
          , typcategory ::  !Char
          , typdelim    ::  !Char
          , typname     :: !ByteString
          , rngsubtype  :: !TypeInfo
          }
  | Composite { typoid      ::  !Oid
              , typcategory ::  !Char
              , typdelim    ::  !Char
              , typname     :: !ByteString
              , typrelid    ::  !Oid
              , attributes  :: !(Vector Attribute)
              }
    deriving (Show)
data Attribute
   = Attribute { attname :: !ByteString
               , atttype :: !TypeInfo
               }
     deriving (Show)