Safe Haskell | None |
---|---|
Language | Haskell2010 |
Hasql.Pipes
Description
This library has 2 high level functions
cursorPipe
to stream a query from postgres DBconnect
to handle connection in 'SafeT IO'
Here is how usage looks like from a production excerpt for a table of samples
mkDB :: ByteString mkDB = [qmb| create table samples ( id uuid not null, time bigint not null, value double precision not null, ); |] streamSamples :: RunSession -> Int64 -- ^ first sample time -> Producer (UUID, Int64, Double) (SafeT IO) () streamSamples (RunSession run) from' = yield from' >-> cursorPipe do run do samplesEncoder do samplesDecoder do Cursor "sample_cursor" do Template [qmb| select * from samples where time >= $1 order by time; |] do 1000 samplesEncoder :: Params Int64 samplesEncoder = param $ E.nonNullable E.int8 samplesDecoder :: Row (UUID, Int64, Double) samplesDecoder = (,,) $ do column . D.nonNullable $ D.uuid * do column . D.nonNullable $ D.int8 * do column . D.nonNullable $ D.float8 localConnect :: Trace IO DatabaseLog -> SafeT IO RunSession localConnect tracer = do connect tracer $ settings "10.1.9.95" 5432 "postgres" "postgres" "postgres" main :: IO () main = do ts <- getPOSIXTime runSafeT $ do run' <- localConnect pPrint runEffect $ streamSamples run' (floor ts - 600) >-> P.print
Synopsis
- newtype Cursor = Cursor ByteString
- newtype Template = Template ByteString
- declareCursor :: Params a -> Cursor -> Template -> Statement a ()
- closeCursor :: Cursor -> Statement () ()
- fetchFromCursor :: Cursor -> Batch -> Result result -> Statement () result
- beginTransaction :: Session ()
- endTransaction :: Session ()
- newtype Batch = Batch Int
- cursorPipe :: (forall b. Session b -> IO b) -> Params z -> Row a -> Cursor -> Template -> Batch -> Pipe z a (SafeT IO) ()
- data DatabaseLog
- newtype RunSession = RunSession (forall a. Session a -> IO a)
- connect :: (DatabaseLog -> IO ()) -> Settings -> SafeT IO RunSession
Documentation
cursor name
Constructors
Cursor ByteString |
Instances
IsString Cursor Source # | |
Defined in Hasql.Pipes Methods fromString :: String -> Cursor # |
query to run
Constructors
Template ByteString |
Instances
IsString Template Source # | |
Defined in Hasql.Pipes Methods fromString :: String -> Template # |
Arguments
:: Params a | paramenters encoding |
-> Cursor | cursor name |
-> Template | query template |
-> Statement a () |
a statement to declare a cursor parametrized over some parameters
Arguments
:: Cursor | cursor name |
-> Batch | max number of rows to fetch |
-> Result result | row decoders |
-> Statement () result |
a statement to fetch given number of rows from cursor forward and apply decoders
beginTransaction :: Session () Source #
endTransaction :: Session () Source #
number of rows
Arguments
:: (forall b. Session b -> IO b) | execute a session command |
-> Params z | query parameters encoders |
-> Row a | row decoders |
-> Cursor | desidered cursor name |
-> Template | query template |
-> Batch | number of rows to repeat fetching |
-> Pipe z a (SafeT IO) () |
stream rows for queries of the same template
data DatabaseLog Source #
Constructors
ConnectionReady | |
ConnectionClosed | |
ConnectionFailed ConnectionError | |
QueryFailed QueryError |
Instances
Show DatabaseLog Source # | |
Defined in Hasql.Pipes Methods showsPrec :: Int -> DatabaseLog -> ShowS # show :: DatabaseLog -> String # showList :: [DatabaseLog] -> ShowS # |
newtype RunSession Source #
Constructors
RunSession (forall a. Session a -> IO a) |
connect :: (DatabaseLog -> IO ()) -> Settings -> SafeT IO RunSession Source #