selda-0.5.2.0: Multi-backend, high-level EDSL for interacting with SQL databases.
Safe HaskellSafe-Inferred
LanguageHaskell2010

Database.Selda.Backend

Description

API for building Selda backends and adding support for more types in queries.

Synopsis

Documentation

class MonadIO m => MonadSelda m where Source #

Some monad with Selda SQL capabilitites.

Minimal complete definition

withConnection

Associated Types

type Backend m Source #

Type of database backend used by m.

Methods

withConnection :: (SeldaConnection (Backend m) -> m a) -> m a Source #

Pass a Selda connection to the given computation and execute it. After the computation finishes, withConnection is free to do anything it likes to the connection, including closing it or giving it to another Selda computation. Thus, the computation must take care never to return or otherwise access the connection after returning.

transact :: m a -> m a Source #

Perform the given computation as a transaction. Implementations must ensure that subsequent calls to withConnection within the same transaction always passes the same connection to its argument.

Instances

Instances details
(MonadIO m, MonadMask m) => MonadSelda (SeldaT b m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Associated Types

type Backend (SeldaT b m) Source #

Methods

withConnection :: (SeldaConnection (Backend (SeldaT b m)) -> SeldaT b m a) -> SeldaT b m a Source #

transact :: SeldaT b m a -> SeldaT b m a Source #

data SeldaT b m a Source #

Monad transformer adding Selda SQL capabilities.

Instances

Instances details
MonadTrans (SeldaT b) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

lift :: Monad m => m a -> SeldaT b m a #

MonadFail m => MonadFail (SeldaT b m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

fail :: String -> SeldaT b m a #

MonadIO m => MonadIO (SeldaT b m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

liftIO :: IO a -> SeldaT b m a #

Applicative m => Applicative (SeldaT b m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

pure :: a -> SeldaT b m a #

(<*>) :: SeldaT b m (a -> b0) -> SeldaT b m a -> SeldaT b m b0 #

liftA2 :: (a -> b0 -> c) -> SeldaT b m a -> SeldaT b m b0 -> SeldaT b m c #

(*>) :: SeldaT b m a -> SeldaT b m b0 -> SeldaT b m b0 #

(<*) :: SeldaT b m a -> SeldaT b m b0 -> SeldaT b m a #

Functor m => Functor (SeldaT b m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

fmap :: (a -> b0) -> SeldaT b m a -> SeldaT b m b0 #

(<$) :: a -> SeldaT b m b0 -> SeldaT b m a #

Monad m => Monad (SeldaT b m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

(>>=) :: SeldaT b m a -> (a -> SeldaT b m b0) -> SeldaT b m b0 #

(>>) :: SeldaT b m a -> SeldaT b m b0 -> SeldaT b m b0 #

return :: a -> SeldaT b m a #

MonadCatch m => MonadCatch (SeldaT b m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

catch :: Exception e => SeldaT b m a -> (e -> SeldaT b m a) -> SeldaT b m a #

MonadMask m => MonadMask (SeldaT b m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

mask :: ((forall a. SeldaT b m a -> SeldaT b m a) -> SeldaT b m b0) -> SeldaT b m b0 #

uninterruptibleMask :: ((forall a. SeldaT b m a -> SeldaT b m a) -> SeldaT b m b0) -> SeldaT b m b0 #

generalBracket :: SeldaT b m a -> (a -> ExitCase b0 -> SeldaT b m c) -> (a -> SeldaT b m b0) -> SeldaT b m (b0, c) #

MonadThrow m => MonadThrow (SeldaT b m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

throwM :: Exception e => e -> SeldaT b m a #

(MonadIO m, MonadMask m) => MonadSelda (SeldaT b m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Associated Types

type Backend (SeldaT b m) Source #

Methods

withConnection :: (SeldaConnection (Backend (SeldaT b m)) -> SeldaT b m a) -> SeldaT b m a Source #

transact :: SeldaT b m a -> SeldaT b m a Source #

type Backend (SeldaT b m) Source # 
Instance details

Defined in Database.Selda.Backend.Internal

type Backend (SeldaT b m) = b

type SeldaM b = SeldaT b IO Source #

The simplest form of Selda computation; SeldaT specialized to IO.

data SeldaError Source #

Thrown by any function in SeldaT if an error occurs.

Constructors

DbError String

Unable to open or connect to database.

SqlError String

An error occurred while executing query.

UnsafeError String

An error occurred due to improper use of an unsafe function.

data StmtID Source #

A prepared statement identifier. Guaranteed to be unique per application.

Instances

Instances details
Show StmtID Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Eq StmtID Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Methods

(==) :: StmtID -> StmtID -> Bool #

(/=) :: StmtID -> StmtID -> Bool #

Ord StmtID Source # 
Instance details

Defined in Database.Selda.Backend.Internal

data BackendID Source #

Uniquely identifies some particular backend.

When publishing a new backend, consider submitting a pull request with a constructor for your backend instead of using the Other constructor.

Constructors

SQLite 
PostgreSQL 
Other Text 

type QueryRunner a = Text -> [Param] -> IO a Source #

A function which executes a query and gives back a list of extensible tuples; one tuple per result row, and one tuple element per column.

data SeldaBackend b Source #

A collection of functions making up a Selda backend.

Constructors

SeldaBackend 

Fields

data SqlValue where Source #

Some value that is representable in SQL.

Instances

Instances details
Show SqlValue Source # 
Instance details

Defined in Database.Selda.SqlType

data IndexMethod Source #

Method to use for indexing with indexedUsing. Index methods are ignored by the SQLite backend, as SQLite doesn't support different index methods.

Constructors

BTreeIndex 
HashIndex 

data Param where Source #

A parameter to a prepared SQL statement.

Constructors

Param :: !(Lit a) -> Param 

Instances

Instances details
Show Param Source # 
Instance details

Defined in Database.Selda.SQL

Methods

showsPrec :: Int -> Param -> ShowS #

show :: Param -> String #

showList :: [Param] -> ShowS #

Eq Param Source # 
Instance details

Defined in Database.Selda.SQL

Methods

(==) :: Param -> Param -> Bool #

(/=) :: Param -> Param -> Bool #

Ord Param Source # 
Instance details

Defined in Database.Selda.SQL

Methods

compare :: Param -> Param -> Ordering #

(<) :: Param -> Param -> Bool #

(<=) :: Param -> Param -> Bool #

(>) :: Param -> Param -> Bool #

(>=) :: Param -> Param -> Bool #

max :: Param -> Param -> Param #

min :: Param -> Param -> Param #

data ColAttr Source #

Column attributes such as nullability, auto increment, etc. When adding elements, make sure that they are added in the order required by SQL syntax, as this list is only sorted before being pretty-printed.

Instances

Instances details
Show ColAttr Source # 
Instance details

Defined in Database.Selda.Table.Type

Eq ColAttr Source # 
Instance details

Defined in Database.Selda.Table.Type

Methods

(==) :: ColAttr -> ColAttr -> Bool #

(/=) :: ColAttr -> ColAttr -> Bool #

Ord ColAttr Source # 
Instance details

Defined in Database.Selda.Table.Type

data AutoIncType Source #

Strongly or weakly auto-incrementing primary key?

Constructors

Weak 
Strong 

data PPConfig Source #

Backend-specific configuration for the SQL pretty-printer.

Constructors

PPConfig 

Fields

  • ppType :: SqlTypeRep -> Text

    The SQL type name of the given type.

    This function should be used everywhere a type is needed to be printed but in primary keys position. This is due to the fact that some backends might have a special representation of primary keys (using sequences are such). If you have such a need, please use the ppTypePK record instead.

  • ppTypeHook :: SqlTypeRep -> [ColAttr] -> (SqlTypeRep -> Text) -> Text

    Hook that allows you to modify ppType output.

  • ppTypePK :: SqlTypeRep -> Text

    The SQL type name of the given type for primary keys uses.

  • ppPlaceholder :: Int -> Text

    Parameter placeholder for the nth parameter.

  • ppColAttrs :: [ColAttr] -> Text

    List of column attributes.

  • ppColAttrsHook :: SqlTypeRep -> [ColAttr] -> ([ColAttr] -> Text) -> Text

    Hook that allows you to modify ppColAttrs output.

  • ppAutoIncInsert :: Text

    The value used for the next value for an auto-incrementing column. For instance, DEFAULT for PostgreSQL, and NULL for SQLite.

  • ppMaxInsertParams :: Maybe Int

    Insert queries may have at most this many parameters; if an insertion has more parameters than this, it will be chunked.

    Note that only insertions of multiple rows are chunked. If your table has more than this many columns, you should really rethink your database design.

  • ppIndexMethodHook :: IndexMethod -> Text

    CREATE INDEX suffix to indicate that the index should use the given index method.

defPPConfig :: PPConfig Source #

Default settings for pretty-printing. Geared towards SQLite.

The default definition of ppTypePK is 'defType, so that you don’t have to do anything special if you don’t use special types for primary keys.

data TableName Source #

Name of a database table.

Instances

Instances details
IsString TableName Source # 
Instance details

Defined in Database.Selda.Types

Show TableName Source # 
Instance details

Defined in Database.Selda.Types

Eq TableName Source # 
Instance details

Defined in Database.Selda.Types

Ord TableName Source # 
Instance details

Defined in Database.Selda.Types

data ColName Source #

Name of a database column.

Instances

Instances details
IsString ColName Source # 
Instance details

Defined in Database.Selda.Types

Methods

fromString :: String -> ColName #

Show ColName Source # 
Instance details

Defined in Database.Selda.Types

Eq ColName Source # 
Instance details

Defined in Database.Selda.Types

Methods

(==) :: ColName -> ColName -> Bool #

(/=) :: ColName -> ColName -> Bool #

Ord ColName Source # 
Instance details

Defined in Database.Selda.Types

data TableInfo Source #

Comprehensive information about a table.

Constructors

TableInfo 

Fields

Instances

Instances details
Show TableInfo Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Eq TableInfo Source # 
Instance details

Defined in Database.Selda.Backend.Internal

data ColumnInfo Source #

Comprehensive information about a column.

Constructors

ColumnInfo 

Fields

Instances

Instances details
Show ColumnInfo Source # 
Instance details

Defined in Database.Selda.Backend.Internal

Eq ColumnInfo Source # 
Instance details

Defined in Database.Selda.Backend.Internal

tableInfo :: Table a -> TableInfo Source #

Get the column information for each column in the given table.

fromColInfo :: ColInfo -> ColumnInfo Source #

Convert a ColInfo into a ColumnInfo.

mkTableName :: Text -> TableName Source #

Create a column name.

mkColName :: Text -> ColName Source #

Create a column name.

fromTableName :: TableName -> Text Source #

Convert a table name into a string, with quotes.

fromColName :: ColName -> Text Source #

Convert a column name into a string, with quotes.

rawTableName :: TableName -> Text Source #

Convert a table name into a string, without quotes.

newConnection :: MonadIO m => SeldaBackend b -> Text -> m (SeldaConnection b) Source #

Create a new Selda connection for the given backend and database identifier string.

allStmts :: SeldaConnection b -> IO [(StmtID, Dynamic)] Source #

Get all statements and their corresponding identifiers for the current connection.

withBackend :: MonadSelda m => (SeldaBackend (Backend m) -> m a) -> m a Source #

Get the backend in use by the computation.

runSeldaT :: (MonadIO m, MonadMask m) => SeldaT b m a -> SeldaConnection b -> m a Source #

Run a Selda transformer. Backends should use this to implement their withX functions.

seldaClose :: MonadIO m => SeldaConnection b -> m () Source #

Close a reusable Selda connection. Closing a connection while in use is undefined. Passing a closed connection to runSeldaT results in a SeldaError being thrown. Closing a connection more than once is a no-op.

data UUID #

Type representing Universally Unique Identifiers (UUID) as specified in RFC 4122.

Instances

Instances details
Data UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UUID -> c UUID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UUID #

toConstr :: UUID -> Constr #

dataTypeOf :: UUID -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c UUID) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UUID) #

gmapT :: (forall b. Data b => b -> b) -> UUID -> UUID #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UUID -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UUID -> r #

gmapQ :: (forall d. Data d => d -> u) -> UUID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UUID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UUID -> m UUID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UUID -> m UUID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UUID -> m UUID #

Storable UUID

This Storable instance uses the memory layout as described in RFC 4122, but in contrast to the Binary instance, the fields are stored in host byte order.

Instance details

Defined in Data.UUID.Types.Internal

Methods

sizeOf :: UUID -> Int #

alignment :: UUID -> Int #

peekElemOff :: Ptr UUID -> Int -> IO UUID #

pokeElemOff :: Ptr UUID -> Int -> UUID -> IO () #

peekByteOff :: Ptr b -> Int -> IO UUID #

pokeByteOff :: Ptr b -> Int -> UUID -> IO () #

peek :: Ptr UUID -> IO UUID #

poke :: Ptr UUID -> UUID -> IO () #

Read UUID 
Instance details

Defined in Data.UUID.Types.Internal

Show UUID

Pretty prints a UUID (without quotation marks). See also toString.

>>> show nil
"00000000-0000-0000-0000-000000000000"
Instance details

Defined in Data.UUID.Types.Internal

Methods

showsPrec :: Int -> UUID -> ShowS #

show :: UUID -> String #

showList :: [UUID] -> ShowS #

Binary UUID

This Binary instance is compatible with RFC 4122, storing the fields in network order as 16 bytes.

Instance details

Defined in Data.UUID.Types.Internal

Methods

put :: UUID -> Put #

get :: Get UUID #

putList :: [UUID] -> Put #

NFData UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

rnf :: UUID -> () #

Eq UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

(==) :: UUID -> UUID -> Bool #

(/=) :: UUID -> UUID -> Bool #

Ord UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

compare :: UUID -> UUID -> Ordering #

(<) :: UUID -> UUID -> Bool #

(<=) :: UUID -> UUID -> Bool #

(>) :: UUID -> UUID -> Bool #

(>=) :: UUID -> UUID -> Bool #

max :: UUID -> UUID -> UUID #

min :: UUID -> UUID -> UUID #

Hashable UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

hashWithSalt :: Int -> UUID -> Int #

hash :: UUID -> Int #

Random UUID

This Random instance produces insecure version 4 UUIDs as specified in RFC 4122.

Instance details

Defined in Data.UUID.Types.Internal

Methods

randomR :: RandomGen g => (UUID, UUID) -> g -> (UUID, g) #

random :: RandomGen g => g -> (UUID, g) #

randomRs :: RandomGen g => (UUID, UUID) -> g -> [UUID] #

randoms :: RandomGen g => g -> [UUID] #

Uniform UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

uniformM :: StatefulGen g m => g -> m UUID #

IsUUID UUID Source # 
Instance details

Defined in Database.Selda

Methods

uuid :: UUID -> UUID Source #

SqlType UUID Source #

defaultValue for UUIDs is the all-zero RFC4122 nil UUID.

Instance details

Defined in Database.Selda.SqlType

Lift UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

lift :: Quote m => UUID -> m Exp #

liftTyped :: forall (m :: Type -> Type). Quote m => UUID -> Code m UUID #

data UUID' a Source #

An UUID identifying a database row.

Instances

Instances details
Generic (UUID' a) Source # 
Instance details

Defined in Database.Selda.SqlType

Associated Types

type Rep (UUID' a) :: Type -> Type #

Methods

from :: UUID' a -> Rep (UUID' a) x #

to :: Rep (UUID' a) x -> UUID' a #

Show (UUID' a) Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

showsPrec :: Int -> UUID' a -> ShowS #

show :: UUID' a -> String #

showList :: [UUID' a] -> ShowS #

Eq (UUID' a) Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

(==) :: UUID' a -> UUID' a -> Bool #

(/=) :: UUID' a -> UUID' a -> Bool #

Ord (UUID' a) Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

compare :: UUID' a -> UUID' a -> Ordering #

(<) :: UUID' a -> UUID' a -> Bool #

(<=) :: UUID' a -> UUID' a -> Bool #

(>) :: UUID' a -> UUID' a -> Bool #

(>=) :: UUID' a -> UUID' a -> Bool #

max :: UUID' a -> UUID' a -> UUID' a #

min :: UUID' a -> UUID' a -> UUID' a #

IsUUID (UUID' a) Source # 
Instance details

Defined in Database.Selda

Methods

uuid :: UUID -> UUID' a Source #

Typeable a => SqlType (UUID' a) Source #

defaultValue for UUIDs is the all-zero RFC4122 nil UUID.

Instance details

Defined in Database.Selda.SqlType

type Rep (UUID' a) Source # 
Instance details

Defined in Database.Selda.SqlType

type Rep (UUID' a) = D1 ('MetaData "UUID'" "Database.Selda.SqlType" "selda-0.5.2.0-BxjrPcn64wf9X9ipyvItC2" 'True) (C1 ('MetaCons "UUID" 'PrefixI 'True) (S1 ('MetaSel ('Just "untypedUuid") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 UUID)))

data ID a Source #

A typed row identifier. Generic tables should use this instead of RowID. Use untyped to erase the type of a row identifier, and cast from the Database.Selda.Unsafe module if you for some reason need to add a type to a row identifier.

Instances

Instances details
Generic (ID a) Source # 
Instance details

Defined in Database.Selda.SqlType

Associated Types

type Rep (ID a) :: Type -> Type #

Methods

from :: ID a -> Rep (ID a) x #

to :: Rep (ID a) x -> ID a #

Show (ID a) Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

showsPrec :: Int -> ID a -> ShowS #

show :: ID a -> String #

showList :: [ID a] -> ShowS #

Eq (ID a) Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

(==) :: ID a -> ID a -> Bool #

(/=) :: ID a -> ID a -> Bool #

Ord (ID a) Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

compare :: ID a -> ID a -> Ordering #

(<) :: ID a -> ID a -> Bool #

(<=) :: ID a -> ID a -> Bool #

(>) :: ID a -> ID a -> Bool #

(>=) :: ID a -> ID a -> Bool #

max :: ID a -> ID a -> ID a #

min :: ID a -> ID a -> ID a #

Typeable a => SqlOrd (ID a) Source # 
Instance details

Defined in Database.Selda

Typeable a => SqlType (ID a) Source # 
Instance details

Defined in Database.Selda.SqlType

type Rep (ID a) Source # 
Instance details

Defined in Database.Selda.SqlType

type Rep (ID a) = D1 ('MetaData "ID" "Database.Selda.SqlType" "selda-0.5.2.0-BxjrPcn64wf9X9ipyvItC2" 'True) (C1 ('MetaCons "ID" 'PrefixI 'True) (S1 ('MetaSel ('Just "untyped") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 RowID)))

data RowID Source #

A row identifier for some table. This is the type of auto-incrementing primary keys.

Instances

Instances details
Generic RowID Source # 
Instance details

Defined in Database.Selda.SqlType

Associated Types

type Rep RowID :: Type -> Type #

Methods

from :: RowID -> Rep RowID x #

to :: Rep RowID x -> RowID #

Show RowID Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

showsPrec :: Int -> RowID -> ShowS #

show :: RowID -> String #

showList :: [RowID] -> ShowS #

Eq RowID Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

(==) :: RowID -> RowID -> Bool #

(/=) :: RowID -> RowID -> Bool #

Ord RowID Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

compare :: RowID -> RowID -> Ordering #

(<) :: RowID -> RowID -> Bool #

(<=) :: RowID -> RowID -> Bool #

(>) :: RowID -> RowID -> Bool #

(>=) :: RowID -> RowID -> Bool #

max :: RowID -> RowID -> RowID #

min :: RowID -> RowID -> RowID #

SqlOrd RowID Source # 
Instance details

Defined in Database.Selda

SqlType RowID Source # 
Instance details

Defined in Database.Selda.SqlType

type Rep RowID Source # 
Instance details

Defined in Database.Selda.SqlType

type Rep RowID = D1 ('MetaData "RowID" "Database.Selda.SqlType" "selda-0.5.2.0-BxjrPcn64wf9X9ipyvItC2" 'True) (C1 ('MetaCons "RowID" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int64)))

data SqlValue where Source #

Some value that is representable in SQL.

Instances

Instances details
Show SqlValue Source # 
Instance details

Defined in Database.Selda.SqlType

data Lit a where Source #

An SQL literal.

Constructors

LText :: !Text -> Lit Text 
LInt32 :: !Int32 -> Lit Int32 
LInt64 :: !Int64 -> Lit Int64 
LDouble :: !Double -> Lit Double 
LBool :: !Bool -> Lit Bool 
LDateTime :: !UTCTime -> Lit UTCTime 
LDate :: !Day -> Lit Day 
LTime :: !TimeOfDay -> Lit TimeOfDay 
LJust :: SqlType a => !(Lit a) -> Lit (Maybe a) 
LBlob :: !ByteString -> Lit ByteString 
LNull :: SqlType a => Lit (Maybe a) 
LCustom :: SqlTypeRep -> Lit a -> Lit b 
LUUID :: !UUID -> Lit UUID 

Instances

Instances details
Show (Lit a) Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

showsPrec :: Int -> Lit a -> ShowS #

show :: Lit a -> String #

showList :: [Lit a] -> ShowS #

Eq (Lit a) Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

(==) :: Lit a -> Lit a -> Bool #

(/=) :: Lit a -> Lit a -> Bool #

Ord (Lit a) Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

compare :: Lit a -> Lit a -> Ordering #

(<) :: Lit a -> Lit a -> Bool #

(<=) :: Lit a -> Lit a -> Bool #

(>) :: Lit a -> Lit a -> Bool #

(>=) :: Lit a -> Lit a -> Bool #

max :: Lit a -> Lit a -> Lit a #

min :: Lit a -> Lit a -> Lit a #

class (Typeable a, Bounded a, Enum a) => SqlEnum a where Source #

Any type that's bounded, enumerable and has a text representation, and thus representable as a Selda enumerable.

While it would be more efficient to store enumerables as integers, this makes hand-rolled SQL touching the values inscrutable, and will break if the user a) derives Enum and b) changes the order of their constructors. Long-term, this should be implemented in PostgreSQL as a proper enum anyway, which mostly renders the performance argument moot.

Methods

toText :: a -> Text Source #

fromText :: Text -> a Source #

Instances

Instances details
(Typeable a, Bounded a, Enum a, Show a, Read a) => SqlEnum a Source # 
Instance details

Defined in Database.Selda.SqlType

Methods

toText :: a -> Text Source #

fromText :: Text -> a Source #

class Typeable a => SqlType a where Source #

Any datatype representable in (Selda's subset of) SQL.

Minimal complete definition

Nothing

Methods

mkLit :: a -> Lit a Source #

Create a literal of this type.

default mkLit :: (Typeable a, SqlEnum a) => a -> Lit a Source #

sqlType :: Proxy a -> SqlTypeRep Source #

The SQL representation for this type.

fromSql :: SqlValue -> a Source #

Convert an SqlValue into this type.

default fromSql :: (Typeable a, SqlEnum a) => SqlValue -> a Source #

defaultValue :: Lit a Source #

Default value when using def at this type.

default defaultValue :: (Typeable a, SqlEnum a) => Lit a Source #

Instances

Instances details
SqlType Int32 Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType Int64 Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType ByteString Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType ByteString Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType Ordering Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType RowID Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType Text Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType Text Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType Day Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType UTCTime Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType TimeOfDay Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType UUID Source #

defaultValue for UUIDs is the all-zero RFC4122 nil UUID.

Instance details

Defined in Database.Selda.SqlType

SqlType Bool Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType Double Source # 
Instance details

Defined in Database.Selda.SqlType

SqlType Int Source # 
Instance details

Defined in Database.Selda.SqlType

(TypeError ((('Text "'Only " :<>: 'ShowType a) :<>: 'Text "' is not a proper SQL type.") :$$: 'Text "Use 'the' to access the value of the column.") :: Constraint, Typeable a) => SqlType (Only a) Source # 
Instance details

Defined in Database.Selda

Typeable a => SqlType (ID a) Source # 
Instance details

Defined in Database.Selda.SqlType

Typeable a => SqlType (UUID' a) Source #

defaultValue for UUIDs is the all-zero RFC4122 nil UUID.

Instance details

Defined in Database.Selda.SqlType

SqlType a => SqlType (Maybe a) Source # 
Instance details

Defined in Database.Selda.SqlType

sqlDateTimeFormat :: String Source #

Format string used to represent date and time when representing timestamps as text. If at all possible, use SqlUTCTime instead.

sqlDateFormat :: String Source #

Format string used to represent date when representing dates as text. If at all possible, use SqlDate instead.

sqlTimeFormat :: String Source #

Format string used to represent time of day when representing time as text. If at all possible, use SqlTime instead.

litType :: Lit a -> SqlTypeRep Source #

The SQL type representation for the given literal.

compLit :: Lit a -> Lit b -> Ordering Source #

Compare two literals of different type for equality.

invalidRowId :: RowID Source #

A row identifier which is guaranteed to not match any row in any table.

isInvalidRowId :: RowID -> Bool Source #

Is the given row identifier invalid? I.e. is it guaranteed to not match any row in any table?

toRowId :: Int64 -> RowID Source #

Create a row identifier from an integer. Use with caution, preferably only when reading user input.

fromRowId :: RowID -> Int64 Source #

Inspect a row identifier.

typedUuid :: UUID -> UUID' a Source #

Convert an untyped UUID to a typed one. Use sparingly, preferably only during deserialization.

toId :: Int64 -> ID a Source #

Create a typed row identifier from an integer. Use with caution, preferably only when reading user input.

fromId :: ID a -> Int64 Source #

Create a typed row identifier from an integer. Use with caution, preferably only when reading user input.

invalidId :: ID a Source #

A typed row identifier which is guaranteed to not match any row in any table.

isInvalidId :: ID a -> Bool Source #

Is the given typed row identifier invalid? I.e. is it guaranteed to not match any row in any table?