Implementing streaming support
Provided package streaming is installed, the utility is demonstrated with the adapted example from the tutorial as follows:
{-# LANGUAGE DeriveGeneric, OverloadedStrings, OverloadedLabels #-}
module Lib where
import Database.Selda
import Database.Selda.SQLite
import qualified Streaming.Prelude as S
data Pet = Dog | Horse | Dragon
deriving (Show, Read, Bounded, Enum)
instance SqlType Pet
data Person = Person
{ name :: Text
, age :: Int
, pet :: Maybe Pet
} deriving (Generic, Show)
instance SqlRow Person
people :: Table Person
people = table "people" [#name :- primary]
prep = do
createTable people
insert_
people
[ Person "Velvet" 19 (Just Dog)
, Person "Kobayashi" 23 (Just Dragon)
, Person "Miyu" 10 Nothing
]
let q = do
person <- select people
restrict (person ! #age .>= 18)
return (person ! #name :*: person ! #pet)
return q
-- since our stream is Monoid of (), we can use print
main :: IO ()
main =
withSQLite "people.sqlite" $ do
q <- prep
forQuery q $ liftIO . print
-- instead of print, now, we use the singleton function of our streaming library,
-- in our example streaming it is `S.yield`
main2 :: IO ()
main2 =
withSQLite "people.sqlite" $ do
q <- prep
a <- forQuery q $ pure . S.yield
S.print a
-- since we can use Monoids to construct a list, this is how we get back to the "usual" list
main3 :: IO ()
main3 =
withSQLite "people.sqlite" $ do
q <- prep
a <- forQuery q $ pure . (:[])
liftIO $ print a
@benjaminweb can you pls enable maintainer pushes to the branch?
(or merge https://github.com/exaexa/selda/tree/streaming :) )
If we make sure the default batch size is somewhat sane, perhaps we could remove the old backend API (i.e. the one that fetches all results at once) and have the frontend wrap the streaming API? I'm not convinced it makes sense to maintain both? That would also give us some testing for free.
If we make sure the default batch size is somewhat sane, perhaps we could remove the old backend API (i.e. the one that fetches all results at once) and have the frontend wrap the streaming API?
For sqlite I think this might be the case; even normally the results are fetched one by one. For libpq this actually makes difference at runtime (the calls are different and the database may hold stuff for longer). I'll try to ask if there's anything that can get broken by chunking everytime, will report if I find anything.