module Database.PostgreSQL.Store.RowParser (
RowParser,
RowErrorLocation (..),
RowErrorDetail (..),
RowError (..),
rowNumber,
columnNumber,
columnsLeft,
fetchColumn,
peekColumn,
parseColumn,
peekContents,
fetchContents,
parseContents,
skipColumn,
parseResult
) where
import Control.Monad
import Control.Monad.Except
import Control.Monad.Reader
import Control.Monad.State.Strict
import qualified Data.ByteString as B
import qualified Database.PostgreSQL.LibPQ as P
import Database.PostgreSQL.Store.Types
data RowErrorLocation = RowErrorLocation P.Column P.Row
deriving (Show, Eq, Ord)
data RowErrorDetail
= TooFewColumns
| ColumnRejected TypedValue
| ContentsRejected (Maybe B.ByteString)
deriving (Show, Eq, Ord)
data RowError = RowError RowErrorLocation RowErrorDetail
deriving (Show, Eq, Ord)
data ResultInfo = ResultInfo P.Result
P.Column
data RowInput = RowInput ResultInfo
P.Row
newtype RowParser a =
RowParser (ReaderT RowInput (StateT P.Column (ExceptT RowError IO)) a)
deriving (Functor, Applicative, Monad, MonadError RowError)
parseRow :: RowParser a -> RowInput -> ExceptT RowError IO a
parseRow (RowParser parser) rowInfo =
evalStateT (runReaderT parser rowInfo) (P.Col 0)
rowNumber :: RowParser P.Row
rowNumber = RowParser (asks (\ (RowInput _ row) -> row))
columnNumber :: RowParser P.Column
columnNumber = RowParser get
columnsLeft :: RowParser P.Column
columnsLeft = RowParser $ do
RowInput (ResultInfo _ numCols) _ <- ask
curCol <- get
pure (numCols curCol)
nextColumn :: RowParser ()
nextColumn =
RowParser (modify (+ 1))
withColumn :: (P.Result -> P.Row -> P.Column -> RowParser a) -> RowParser a
withColumn action = do
(RowInput (ResultInfo result numColumns) row, col) <- RowParser ((,) <$> ask <*> get)
if col < numColumns then
action result row col
else
throwError (RowError (RowErrorLocation col row) TooFewColumns)
peekColumn :: RowParser TypedValue
peekColumn =
withColumn $ \ result row col -> RowParser $ liftIO $
TypedValue <$> P.ftype result col
<*> fmap (fmap Value) (P.getvalue' result row col)
fetchColumn :: RowParser TypedValue
fetchColumn =
peekColumn <* nextColumn
parseColumn :: (TypedValue -> Maybe a) -> RowParser a
parseColumn proc = do
typedValue <- peekColumn
case proc typedValue of
Just x -> x <$ nextColumn
Nothing -> do
col <- columnNumber
row <- rowNumber
throwError (RowError (RowErrorLocation col row) (ColumnRejected typedValue))
peekContents :: RowParser (Maybe B.ByteString)
peekContents =
withColumn (\ result row col -> RowParser (liftIO (P.getvalue' result row col)))
fetchContents :: RowParser (Maybe B.ByteString)
fetchContents =
peekContents <* nextColumn
parseContents :: (B.ByteString -> Maybe a) -> RowParser a
parseContents proc = do
value <- peekContents
case value >>= proc of
Just x -> x <$ nextColumn
Nothing -> do
col <- columnNumber
row <- rowNumber
throwError (RowError (RowErrorLocation col row) (ContentsRejected value))
skipColumn :: RowParser ()
skipColumn = do
(RowInput (ResultInfo _ numColumns) row, col) <- RowParser ((,) <$> ask <*> get)
if col < numColumns then
nextColumn
else
throwError (RowError (RowErrorLocation col row) TooFewColumns)
parseResult :: P.Result -> RowParser a -> ExceptT RowError IO [a]
parseResult result parser = do
(resultInfo, numRows) <- liftIO $ do
numColumns <- P.nfields result
numRows <- P.ntuples result
pure (ResultInfo result numColumns, numRows)
forM [0 .. numRows 1] (parseRow parser . RowInput resultInfo)