Safe Haskell | None |
---|---|
Language | Haskell2010 |
Internal backend API. Using anything exported from this module may or may not invalidate any safety guarantees made by Selda; use at your own peril.
Synopsis
- newtype StmtID = StmtID Int
- data BackendID
- = SQLite
- | PostgreSQL
- | Other Text
- type QueryRunner a = Text -> [Param] -> IO a
- data SeldaBackend b = SeldaBackend {
- runStmt :: Text -> [Param] -> IO (Int, [[SqlValue]])
- runStmtWithPK :: Text -> [Param] -> IO Int
- prepareStmt :: StmtID -> [SqlTypeRep] -> Text -> IO Dynamic
- runPrepared :: Dynamic -> [Param] -> IO (Int, [[SqlValue]])
- getTableInfo :: TableName -> IO TableInfo
- ppConfig :: PPConfig
- closeConnection :: SeldaConnection b -> IO ()
- backendId :: BackendID
- disableForeignKeys :: Bool -> IO ()
- data SeldaConnection b = SeldaConnection {
- connBackend :: !(SeldaBackend b)
- connDbId :: Text
- connStmts :: !(IORef (IntMap SeldaStmt))
- connClosed :: !(IORef Bool)
- connLock :: !(MVar ())
- data SeldaStmt = SeldaStmt {
- stmtHandle :: !Dynamic
- stmtText :: !Text
- stmtParams :: ![Either Int Param]
- class MonadIO m => MonadSelda m where
- type Backend m
- withConnection :: (SeldaConnection (Backend m) -> m a) -> m a
- transact :: m a -> m a
- newtype SeldaT b m a = S {
- unS :: StateT (SeldaConnection b) m a
- type SeldaM b = SeldaT b IO
- data SeldaError
- data Param where
- data Lit a where
- LText :: !Text -> Lit Text
- LInt :: !Int -> Lit Int
- 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
- data ColAttr
- data AutoIncType
- class Typeable a => SqlType a where
- mkLit :: a -> Lit a
- sqlType :: Proxy a -> SqlTypeRep
- fromSql :: SqlValue -> a
- defaultValue :: Lit a
- data SqlValue where
- data SqlTypeRep
- data PPConfig = PPConfig {
- ppType :: SqlTypeRep -> Text
- ppTypeHook :: SqlTypeRep -> [ColAttr] -> (SqlTypeRep -> Text) -> Text
- ppTypePK :: SqlTypeRep -> Text
- ppPlaceholder :: Int -> Text
- ppColAttrs :: [ColAttr] -> Text
- ppColAttrsHook :: SqlTypeRep -> [ColAttr] -> ([ColAttr] -> Text) -> Text
- ppAutoIncInsert :: Text
- ppMaxInsertParams :: Maybe Int
- ppIndexMethodHook :: IndexMethod -> Text
- defPPConfig :: PPConfig
- data TableInfo = TableInfo {
- tableColumnInfos :: [ColumnInfo]
- tableUniqueGroups :: [[ColName]]
- tablePrimaryKey :: [ColName]
- data ColumnInfo = ColumnInfo {
- colName :: ColName
- colType :: Either Text SqlTypeRep
- colIsAutoPrimary :: Bool
- colIsNullable :: Bool
- colHasIndex :: Bool
- colFKs :: [(TableName, ColName)]
- tableInfo :: Table a -> TableInfo
- fromColInfo :: ColInfo -> ColumnInfo
- isAutoPrimary :: ColAttr -> Bool
- isPrimary :: ColAttr -> Bool
- isUnique :: ColAttr -> Bool
- sqlDateTimeFormat :: String
- sqlDateFormat :: String
- sqlTimeFormat :: String
- freshStmtId :: MonadIO m => m StmtID
- newConnection :: MonadIO m => SeldaBackend b -> Text -> m (SeldaConnection b)
- allStmts :: SeldaConnection b -> IO [(StmtID, Dynamic)]
- runSeldaT :: (MonadIO m, MonadMask m) => SeldaT b m a -> SeldaConnection b -> m a
- withBackend :: MonadSelda m => (SeldaBackend (Backend m) -> m a) -> m a
Documentation
A prepared statement identifier. Guaranteed to be unique per application.
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.
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.
SeldaBackend | |
|
data SeldaConnection b Source #
SeldaConnection | |
|
A prepared statement.
SeldaStmt | |
|
class MonadIO m => MonadSelda m where Source #
Some monad with Selda SQL capabilitites.
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.
Monad transformer adding Selda SQL capabilities.
S | |
|
Instances
data SeldaError Source #
Thrown by any function in SeldaT
if an error occurs.
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. |
Instances
Eq SeldaError Source # | |
Defined in Database.Selda.Backend.Internal (==) :: SeldaError -> SeldaError -> Bool # (/=) :: SeldaError -> SeldaError -> Bool # | |
Show SeldaError Source # | |
Defined in Database.Selda.Backend.Internal showsPrec :: Int -> SeldaError -> ShowS # show :: SeldaError -> String # showList :: [SeldaError] -> ShowS # | |
Exception SeldaError Source # | |
Defined in Database.Selda.Backend.Internal toException :: SeldaError -> SomeException # fromException :: SomeException -> Maybe SeldaError # displayException :: SeldaError -> String # |
A parameter to a prepared SQL statement.
An SQL literal.
LText :: !Text -> Lit Text | |
LInt :: !Int -> Lit Int | |
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 |
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.
data AutoIncType Source #
Strongly or weakly auto-incrementing primary key?
Instances
Eq AutoIncType Source # | |
Defined in Database.Selda.Table.Type (==) :: AutoIncType -> AutoIncType -> Bool # (/=) :: AutoIncType -> AutoIncType -> Bool # | |
Ord AutoIncType Source # | |
Defined in Database.Selda.Table.Type compare :: AutoIncType -> AutoIncType -> Ordering # (<) :: AutoIncType -> AutoIncType -> Bool # (<=) :: AutoIncType -> AutoIncType -> Bool # (>) :: AutoIncType -> AutoIncType -> Bool # (>=) :: AutoIncType -> AutoIncType -> Bool # max :: AutoIncType -> AutoIncType -> AutoIncType # min :: AutoIncType -> AutoIncType -> AutoIncType # | |
Show AutoIncType Source # | |
Defined in Database.Selda.Table.Type showsPrec :: Int -> AutoIncType -> ShowS # show :: AutoIncType -> String # showList :: [AutoIncType] -> ShowS # |
class Typeable a => SqlType a where Source #
Any datatype representable in (Selda's subset of) SQL.
Nothing
Create a literal of this type.
mkLit :: (Typeable a, SqlEnum a) => a -> Lit a Source #
Create a literal of this type.
sqlType :: Proxy a -> SqlTypeRep Source #
The SQL representation for this type.
fromSql :: SqlValue -> a Source #
Convert an SqlValue into this type.
fromSql :: (Typeable a, SqlEnum a) => SqlValue -> a Source #
Convert an SqlValue into this type.
defaultValue :: Lit a Source #
Default value when using def
at this type.
defaultValue :: (Typeable a, SqlEnum a) => Lit a Source #
Default value when using def
at this type.
Instances
SqlType Bool Source # | |
SqlType Double Source # | |
SqlType Int Source # | |
SqlType Ordering Source # | |
SqlType ByteString Source # | |
Defined in Database.Selda.SqlType mkLit :: ByteString -> Lit ByteString Source # sqlType :: Proxy ByteString -> SqlTypeRep Source # fromSql :: SqlValue -> ByteString Source # | |
SqlType ByteString Source # | |
Defined in Database.Selda.SqlType mkLit :: ByteString -> Lit ByteString Source # sqlType :: Proxy ByteString -> SqlTypeRep Source # fromSql :: SqlValue -> ByteString Source # | |
SqlType Text Source # | |
SqlType TimeOfDay Source # | |
SqlType UTCTime Source # | |
SqlType Day Source # | |
SqlType UUID Source # |
|
SqlType RowID Source # | |
SqlType a => SqlType (Maybe a) Source # | |
Typeable a => SqlType (ID a) Source # | |
((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 # | |
Some value that is representable in SQL.
data SqlTypeRep Source #
Representation of an SQL type.
Instances
Eq SqlTypeRep Source # | |
Defined in Database.Selda.SqlType (==) :: SqlTypeRep -> SqlTypeRep -> Bool # (/=) :: SqlTypeRep -> SqlTypeRep -> Bool # | |
Ord SqlTypeRep Source # | |
Defined in Database.Selda.SqlType compare :: SqlTypeRep -> SqlTypeRep -> Ordering # (<) :: SqlTypeRep -> SqlTypeRep -> Bool # (<=) :: SqlTypeRep -> SqlTypeRep -> Bool # (>) :: SqlTypeRep -> SqlTypeRep -> Bool # (>=) :: SqlTypeRep -> SqlTypeRep -> Bool # max :: SqlTypeRep -> SqlTypeRep -> SqlTypeRep # min :: SqlTypeRep -> SqlTypeRep -> SqlTypeRep # | |
Show SqlTypeRep Source # | |
Defined in Database.Selda.SqlType showsPrec :: Int -> SqlTypeRep -> ShowS # show :: SqlTypeRep -> String # showList :: [SqlTypeRep] -> ShowS # |
Backend-specific configuration for the SQL pretty-printer.
PPConfig | |
|
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.
Comprehensive information about a table.
TableInfo | |
|
data ColumnInfo Source #
Comprehensive information about a column.
ColumnInfo | |
|
Instances
Eq ColumnInfo Source # | |
Defined in Database.Selda.Backend.Internal (==) :: ColumnInfo -> ColumnInfo -> Bool # (/=) :: ColumnInfo -> ColumnInfo -> Bool # | |
Show ColumnInfo Source # | |
Defined in Database.Selda.Backend.Internal showsPrec :: Int -> ColumnInfo -> ShowS # show :: ColumnInfo -> String # showList :: [ColumnInfo] -> ShowS # |
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
.
isAutoPrimary :: ColAttr -> Bool Source #
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.
freshStmtId :: MonadIO m => m StmtID Source #
Generate a fresh statement identifier, guaranteed to be unique per process.
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.
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.
withBackend :: MonadSelda m => (SeldaBackend (Backend m) -> m a) -> m a Source #
Get the backend in use by the computation.