Code that is only needed for writing GenericSql backends.
- data Connection = Connection {
- prepare :: String -> IO Statement
- insertSql :: RawName -> [RawName] -> Either String (String, String)
- stmtMap :: IORef (Map String Statement)
- close :: IO ()
- migrateSql :: forall v. PersistEntity v => (String -> IO Statement) -> v -> IO (Either [String] [(Bool, String)])
- begin :: (String -> IO Statement) -> IO ()
- commit :: (String -> IO Statement) -> IO ()
- rollback :: (String -> IO Statement) -> IO ()
- escapeName :: RawName -> String
- noLimit :: String
- data Statement = Statement {
- finalize :: IO ()
- reset :: IO ()
- execute :: [PersistValue] -> IO ()
- withStmt :: forall a m. MonadInvertIO m => [PersistValue] -> (RowPopper m -> m a) -> m a
- withSqlConn :: MonadInvertIO m => IO Connection -> (Connection -> m a) -> m a
- withSqlPool :: MonadInvertIO m => IO Connection -> Int -> (Pool Connection -> m a) -> m a
- type RowPopper m = m (Maybe [PersistValue])
- mkColumns :: PersistEntity val => val -> ([Column], [UniqueDef])
- data Column = Column {}
- type UniqueDef = (RawName, [RawName])
- refName :: RawName -> RawName -> RawName
- tableColumns :: EntityDef -> [(RawName, String, [String])]
- rawFieldName :: (String, String, [String]) -> RawName
- rawTableName :: EntityDef -> RawName
- newtype RawName = RawName {}
Documentation
data Connection Source
Connection | |
|
Statement | |
|
withSqlConn :: MonadInvertIO m => IO Connection -> (Connection -> m a) -> m aSource
withSqlPool :: MonadInvertIO m => IO Connection -> Int -> (Pool Connection -> m a) -> m aSource
type RowPopper m = m (Maybe [PersistValue])Source
mkColumns :: PersistEntity val => val -> ([Column], [UniqueDef])Source
Create the list of columns for the given entity.