| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Database.PSQL.Types
Synopsis
- data TablePrefix
- data Connection
- type PSQLPool = Pool Connection
- data PSQL a
- runPSQL :: TablePrefix -> Connection -> PSQL a -> IO a
- runPSQLPool :: TablePrefix -> PSQLPool -> PSQL a -> IO a
- runPSQLEnv :: HasPSQL env => env -> PSQL a -> IO a
- getTablePrefix :: PSQL TablePrefix
- class HasPSQL u
- psqlPool :: HasPSQL u => u -> PSQLPool
- tablePrefix :: HasPSQL u => u -> TablePrefix
- data SimpleEnv u
- simpleEnv :: Pool Connection -> TablePrefix -> u -> SimpleEnv u
- class HasOtherEnv u a
- otherEnv :: HasOtherEnv u a => a -> u
- data TableName
- getTableName :: TablePrefix -> TableName -> String
- type Columns = [Column]
- createTable :: TableName -> Columns -> PSQL Int64
- constraintPrimaryKey :: TablePrefix -> TableName -> Columns -> Column
- getIndexName :: TablePrefix -> TableName -> IndexName -> String
- data IndexName
- createIndex :: Bool -> TableName -> IndexName -> Columns -> PSQL Int64
- getOnly :: FromRow (Only a) => [Only a] -> Maybe a
- getOnlyDefault :: FromRow (Only a) => a -> [Only a] -> a
- insert :: ToRow a => TableName -> Columns -> a -> PSQL Int64
- insertRet :: (ToRow a, FromRow (Only b)) => TableName -> Columns -> Column -> a -> b -> PSQL b
- insertOrUpdate :: ToRow a => TableName -> Columns -> Columns -> Columns -> a -> PSQL Int64
- update :: ToRow a => TableName -> Columns -> String -> a -> PSQL Int64
- delete :: ToRow a => TableName -> String -> a -> PSQL Int64
- delete_ :: TableName -> PSQL Int64
- count :: ToRow a => TableName -> String -> a -> PSQL Int64
- count_ :: TableName -> PSQL Int64
- select :: (ToRow a, FromRow b) => TableName -> Columns -> String -> a -> From -> Size -> OrderBy -> PSQL [b]
- selectOnly :: (ToRow a, FromRow (Only b)) => TableName -> Column -> String -> a -> From -> Size -> OrderBy -> PSQL [b]
- select_ :: FromRow b => TableName -> Columns -> From -> Size -> OrderBy -> PSQL [b]
- selectOnly_ :: FromRow (Only b) => TableName -> Column -> From -> Size -> OrderBy -> PSQL [b]
- selectOne :: (ToRow a, FromRow b) => TableName -> Columns -> String -> a -> PSQL (Maybe b)
- selectOneOnly :: (ToRow a, FromRow (Only b)) => TableName -> Column -> String -> a -> PSQL (Maybe b)
- type VersionList a = [Version a]
- mergeDatabase :: VersionList a -> PSQL ()
- class FromRow a where
- field :: FromField a => RowParser a
- newtype Only a = Only {- fromOnly :: a
 
- data SqlError = SqlError {}
- data OrderBy
- asc :: String -> OrderBy
- desc :: String -> OrderBy
- none :: OrderBy
Documentation
data TablePrefix Source #
Instances
| Show TablePrefix Source # | |
| Defined in Database.PSQL.Types Methods showsPrec :: Int -> TablePrefix -> ShowS # show :: TablePrefix -> String # showList :: [TablePrefix] -> ShowS # | |
| IsString TablePrefix Source # | |
| Defined in Database.PSQL.Types Methods fromString :: String -> TablePrefix # | |
data Connection #
Instances
| Eq Connection | |
| Defined in Database.PostgreSQL.Simple.Internal | |
type PSQLPool = Pool Connection Source #
runPSQL :: TablePrefix -> Connection -> PSQL a -> IO a Source #
runPSQLPool :: TablePrefix -> PSQLPool -> PSQL a -> IO a Source #
Minimal complete definition
Instances
| HasPSQL (SimpleEnv u) Source # | |
| Defined in Database.PSQL.Types Methods psqlPool :: SimpleEnv u -> PSQLPool Source # tablePrefix :: SimpleEnv u -> TablePrefix Source # | |
tablePrefix :: HasPSQL u => u -> TablePrefix Source #
Instances
| HasOtherEnv u (SimpleEnv u) Source # | |
| Defined in Database.PSQL.Types | |
| HasPSQL (SimpleEnv u) Source # | |
| Defined in Database.PSQL.Types Methods psqlPool :: SimpleEnv u -> PSQLPool Source # tablePrefix :: SimpleEnv u -> TablePrefix Source # | |
simpleEnv :: Pool Connection -> TablePrefix -> u -> SimpleEnv u Source #
class HasOtherEnv u a Source #
Minimal complete definition
Instances
| HasOtherEnv u (SimpleEnv u) Source # | |
| Defined in Database.PSQL.Types | |
otherEnv :: HasOtherEnv u a => a -> u Source #
getTableName :: TablePrefix -> TableName -> String Source #
constraintPrimaryKey :: TablePrefix -> TableName -> Columns -> Column Source #
getIndexName :: TablePrefix -> TableName -> IndexName -> String Source #
insertRet :: (ToRow a, FromRow (Only b)) => TableName -> Columns -> Column -> a -> b -> PSQL b Source #
select :: (ToRow a, FromRow b) => TableName -> Columns -> String -> a -> From -> Size -> OrderBy -> PSQL [b] Source #
selectOnly :: (ToRow a, FromRow (Only b)) => TableName -> Column -> String -> a -> From -> Size -> OrderBy -> PSQL [b] Source #
selectOnly_ :: FromRow (Only b) => TableName -> Column -> From -> Size -> OrderBy -> PSQL [b] Source #
selectOneOnly :: (ToRow a, FromRow (Only b)) => TableName -> Column -> String -> a -> PSQL (Maybe b) Source #
type VersionList a = [Version a] Source #
mergeDatabase :: VersionList a -> PSQL () Source #
A collection type that can be converted from a sequence of fields. Instances are provided for tuples up to 10 elements and lists of any length.
Note that instances can be defined outside of postgresql-simple, which is often useful. For example, here's an instance for a user-defined pair:
data User = User { name :: String, fileQuota :: Int }
instance FromRow User where
    fromRow = User <$> field <*> field
The number of calls to field must match the number of fields returned
 in a single row of the query result.  Otherwise,  a ConversionFailed
 exception will be thrown.
You can also derive FromRow for your data type using GHC generics, like
 this:
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE DeriveGeneric  #-}
import GHC.Generics (Generic)
import Database.PostgreSQL.Simple (FromRow)
data User = User { name :: String, fileQuota :: Int }
  deriving (Generic, FromRow)
Note that this only works for product types (e.g. records) and does not support sum types or recursive types.
Note that field evaluates its result to WHNF, so the caveats listed in
 mysql-simple and very early versions of postgresql-simple no longer apply.
 Instead, look at the caveats associated with user-defined implementations
 of fromField.
Minimal complete definition
Nothing
Instances
The 1-tuple type or single-value "collection".
This type is structurally equivalent to the
 Identity type, but its intent is more
 about serving as the anonymous 1-tuple type missing from Haskell for attaching
 typeclass instances.
Parameter usage example:
encodeSomething (Only (42::Int))Result usage example:
xs <- decodeSomething
forM_ xs $ \(Only id) -> {- ... -}Instances
| Functor Only | |
| Eq a => Eq (Only a) | |
| Data a => Data (Only a) | |
| Defined in Data.Tuple.Only Methods gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Only a -> c (Only a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Only a) # toConstr :: Only a -> Constr # dataTypeOf :: Only a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Only a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Only a)) # gmapT :: (forall b. Data b => b -> b) -> Only a -> Only a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Only a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Only a -> r # gmapQ :: (forall d. Data d => d -> u) -> Only a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Only a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Only a -> m (Only a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Only a -> m (Only a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Only a -> m (Only a) # | |
| Ord a => Ord (Only a) | |
| Read a => Read (Only a) | |
| Show a => Show (Only a) | |
| Generic (Only a) | |
| NFData a => NFData (Only a) | |
| Defined in Data.Tuple.Only | |
| FromField a => FromRow (Maybe (Only a)) | |
| FromField a => FromRow (Only a) | |
| Defined in Database.PostgreSQL.Simple.FromRow | |
| ToField a => ToRow (Only a) | |
| Defined in Database.PostgreSQL.Simple.ToRow | |
| type Rep (Only a) | |
| Defined in Data.Tuple.Only | |
Constructors
| SqlError | |
| Fields | |
Instances
| Eq SqlError | |
| Show SqlError | |
| Exception SqlError | |
| Defined in Database.PostgreSQL.Simple.Internal Methods toException :: SqlError -> SomeException # fromException :: SomeException -> Maybe SqlError # displayException :: SqlError -> String # | |
Instances
| Eq OrderBy Source # | |
| Show OrderBy Source # | |
| Generic OrderBy Source # | |
| Hashable OrderBy Source # | |
| Defined in Database.PSQL.Types | |
| type Rep OrderBy Source # | |
| Defined in Database.PSQL.Types type Rep OrderBy = D1 (MetaData "OrderBy" "Database.PSQL.Types" "psql-utils-0.2.0.0-Deho2j0iuFX5udS1yvmz0n" False) (C1 (MetaCons "Desc" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: (C1 (MetaCons "Asc" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 String)) :+: C1 (MetaCons "None" PrefixI False) (U1 :: Type -> Type))) | |