module Database.PostgreSQL.Base.Types
(ConnectInfo(..)
,Connection(..)
,Field(..)
,Result(..)
,Type(..)
,MessageType(..)
,Size(..)
,FormatCode(..)
,Modifier(..)
,ObjectId
,Pool(..)
,PoolState(..)
,ConnectionError(..))
where
import Control.Concurrent.MVar (MVar)
import qualified Data.ByteString as B
import qualified Data.ByteString.Lazy as L
import Data.Int
import Data.Typeable
import Data.Word
import System.IO (Handle)
import Data.IntMap.Strict (IntMap)
import Control.Exception (Exception)
data ConnectionError =
QueryError (Maybe String)
| QueryEmpty
| AuthenticationFailed String
| InitializationError String
| ConnectionLost
| UnsupportedAuthenticationMethod Int32 String
| GeneralError String
deriving (Typeable,Show)
instance Exception ConnectionError where
data ConnectInfo = ConnectInfo {
connectHost :: String
, connectPort :: Word16
, connectUser :: String
, connectPassword :: String
, connectDatabase :: String
} deriving (Eq,Read,Show,Typeable)
data Connection = Connection {
connectionHandle :: MVar (Maybe Handle)
, connectionObjects :: MVar (IntMap Type)
}
data Result =
Result {
resultRows :: [[Maybe B.ByteString]]
,resultDesc :: Maybe [Field]
,resultError :: Maybe L.ByteString
,resultNotices :: [String]
,resultType :: MessageType
,resultTagRows :: Maybe Integer
} deriving Show
data MessageType =
CommandComplete
| RowDescription
| DataRow
| EmptyQueryResponse
| ErrorResponse
| ReadyForQuery
| NoticeResponse
| AuthenticationOk
| Query
| PasswordMessage
| UnknownMessageType
deriving (Show,Eq)
data Field = Field {
fieldType :: Type
,fieldFormatCode :: FormatCode
} deriving Show
data Type =
Short
| Long
| LongLong
| Decimal
| Numeric
| Real
| DoublePrecision
| CharVarying
| Characters
| Text
| Boolean
| Timestamp
| TimestampWithZone
| Date
| Time
deriving (Eq,Enum,Show)
data Size = Varying | Size Int16
deriving (Eq,Ord,Show)
data FormatCode = TextCode | BinaryCode
deriving (Eq,Ord,Show)
data Modifier = Modifier
type ObjectId = Int
data PoolState = PoolState {
poolConnections :: [Connection]
, poolConnectInfo :: ConnectInfo
}
newtype Pool = Pool { unPool :: MVar PoolState }