module Database.PostgreSQL.Store.RowParser (
RowParser,
RowErrorLocation (..),
RowErrorDetail (..),
RowError (..),
processResultWith,
(>>=$),
(>>$),
(<*>$),
finish,
cancel,
skipColumns,
nonNullCheck,
processContent,
retrieveColumn,
retrieveContent
) where
import GHC.TypeLits
import Control.Monad.Except
import qualified Data.ByteString as B
import Data.Proxy
import Database.PostgreSQL.Store.Types
import qualified Database.PostgreSQL.LibPQ as P
data RowErrorLocation = RowErrorLocation P.Column P.Row
deriving (Show, Eq, Ord)
data RowErrorDetail
= TooFewColumns
| ColumnRejected
deriving (Show, Eq, Ord)
data RowError = RowError RowErrorLocation RowErrorDetail
deriving (Show, Eq, Ord)
type M = ExceptT RowError IO
newtype RowParser (w :: Nat) a = RowParser { runProcessor :: P.Result -> P.Row -> P.Column -> M a }
instance Functor (RowParser w) where
fmap f (RowParser action) =
RowParser (\ result row col -> f <$> action result row col)
processResultWith :: forall a n. (KnownNat n) => P.Result -> RowParser n a -> ExceptT RowError IO [a]
processResultWith result (RowParser run) = do
cols <- lift (P.nfields result)
when (cols < toEnum totalWidth) $
throwError (RowError (RowErrorLocation 0 0) TooFewColumns)
rows <- lift (P.ntuples result)
forM [0 .. rows 1] (\ row -> run result row 0)
where
totalWidth = fromIntegral (natVal @n Proxy)
finish :: a -> RowParser 0 a
finish x = RowParser (\ _ _ _ -> pure x)
cancel :: RowErrorDetail -> RowParser 0 a
cancel detail = RowParser (\ _ row col -> throwError (RowError (RowErrorLocation col row) detail))
infixl 1 >>=$
(>>=$) :: forall a v b w. (KnownNat v)
=> RowParser v a -> (a -> RowParser w b) -> RowParser (v + w) b
proc >>=$ func =
RowParser $ \ result row col -> do
x <- runProcessor proc result row col :: M a
runProcessor (func x) result row (col + fromIntegral (natVal @v Proxy))
infixl 1 >>$
(>>$) :: forall a v b w. (KnownNat v)
=> RowParser v a -> RowParser w b -> RowParser (v + w) b
p1 >>$ p2 = p1 >>=$ const p2
infixl 4 <*>$
(<*>$) :: forall a v b w. (KnownNat v)
=> RowParser v (a -> b) -> RowParser w a -> RowParser (v + w) b
pf <*>$ px = pf >>=$ (<$> px)
skipColumns :: RowParser n ()
skipColumns = RowParser (\ _ _ _ -> pure ())
nonNullCheck :: Int -> RowParser 0 Bool
nonNullCheck n =
RowParser $ \ result row col ->
not . or <$> lift (forM [col .. col + (toEnum n 1)] (P.getisnull result row))
processContent :: (Oid -> Maybe B.ByteString -> Maybe a) -> RowParser 1 a
processContent proc =
RowParser $ \ result row col -> do
res <- lift (proc <$> P.ftype result col <*> P.getvalue' result row col)
case res of
Just cnt -> pure cnt
Nothing -> throwError (RowError (RowErrorLocation col row) ColumnRejected)
retrieveColumn :: RowParser 1 (Oid, Maybe B.ByteString)
retrieveColumn = processContent (curry Just)
retrieveContent :: RowParser 1 B.ByteString
retrieveContent = processContent (const id)