Frames-beam-0.1.0.0: A library for accessing Postgres tables as in-memory data structures.

Copyright(c) Gagandeep Bhatia 2018
LicenseBSD3
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Frames.SQL.Beam.Postgres

Contents

Description

This library provides a way to access Postgres tables as data frames by providing helpers for generating types (at compile time) corresponding to a database schema (Frames.SQL.Beam.Postgres.BeamSchemaGen) and canned queries to execute against a database (Frames.SQL.Beam.Postgres.Query) instance. Additionally, provides utilities to convert plain Haskell records (i.e. the format of query results) to vinyl records (upon which the Frames library is based) (Frames.SQL.Beam.Postgres.Vinylize). Can be used for interactive exploration by loading all data in-memory at once (and converting to a data frame), and also in a constant memory streaming mode (Frames.SQL.Beam.Postgres.Streaming).

Synopsis

Usage Example

A. Interactive Workflow Steps

1. Bootstrap database schema: In a new project, assume a file Example.hs is present in the src directory with the code below. You may of course change the string passed to genBeamSchema to match your database instance of interest.

   -- Example.hs
   -- Extensions elided
   module Example where

   import qualified Data.Conduit.List        as CL
   import qualified Data.Vinyl.Functor       as VF
   import qualified Frames                   as F
   import           Frames.SQL.Beam.Postgres

   $(genBeamSchema "host=localhost dbname=shoppingcart1")
   

2. Next, execute stack build or stack ghci. This compilation step, if completed without any errors, will establish a connection to your database instance of interest, read its schema, generate corresponding Haskell types and put them in a module named NewBeamSchema in your src directory (the file creation step is also part of the compilation process).

3. Assuming step 2 worked fine for you and you were using the test DB-dump from the data folder in the repo, you should now have a module with code matching that in the test/NewBeamSchema.hs file of this repository. In case you used some other database instance of your own, your generated module would look different.

Import this module into Example:

   -- Example.hs
   -- Extensions elided
   module Example where

   import qualified Data.Conduit.List        as CL
   import qualified Data.Vinyl.Functor       as VF
   import qualified Frames                   as F
   import           Frames.SQL.Beam.Postgres

   import NewBeamSchema


   $(genBeamSchema "host=localhost dbname=shoppingcart1")
   

4. Let's assume the table of interest is Cart_usersT. We want to pull rows from this table into a data frame to explore it interactively from ghci. Note that beam query results are lists of plain Haskell records whereas Frames requires a list of vinyl records. In order to make this conversion, we add the following two invokations of code-generating (Template-Haskell) functions to Example:

   -- Example.hs
   -- rest of the module elided

   import NewBeamSchema


   $(genBeamSchema "host=localhost dbname=shoppingcart1")

   deriveGeneric ''Cart_usersT
   deriveVinyl ''Cart_usersT
   

...and build your project. This will add some additional code into the Example module. You can inspect this code by adding the appropriate compiler flags to your .cabal file.

5. Querying the DB: In this step we will execute a 'SELECT * FROM tbl WHERE...' query and convert the results to a data frame. Note that the table declaration (_cart_users) and the database declaration (db) are exported by the NewBeamSchema module. More importantly, these declarations are autogenerated at compile time, so in case new tables are added, the corresponding declarations are automatically available for use.

   -- Example.hs
   connString :: ByteString
   connString = "host=localhost dbname=shoppingcart1"

   -- selects n rows from the specified table in the db.
   loadRows1 :: Int -> IO [(Cart_usersT Identity)]
   loadRows1 n =
     withConnection connString $
       bulkSelectAllRows _cart_users db n

   loadRows2 :: Int -> IO [(Cart_usersT Identity)]
   loadRows2 n =
     withConnection connString $
       bulkSelectAllRowsWhere _cart_users db n (c -> (_cart_usersFirst_name c) `like_` "J%")
   

Notice the lambda passed to bulkSelectAllRowsWhere in loadRows2. This is a 'filter lambda' that forms the `WHERE ...` part of the SQL query and is executed at the DB-level. We will see how to create our own 'filter lambdas' in another section below. For now, if we were to enter ghci by executing stack ghci after adding the above code:

   ghci>res1 <- loadRows1 5
   ghci>:t res1
   res1 :: [Cart_usersT Identity]
   ghci>:t (map createRecId res1)
   (map createRecId res1)
     :: [F.Rec
           VF.Identity
           '["_cart_usersEmail" F.:-> Text,
             "_cart_usersFirst_name" F.:-> Text,
             "_cart_usersLast_name" F.:-> Text,
             "_cart_usersIs_member" F.:-> Bool,
             "_cart_usersDays_in_queue" F.:-> Int]]
   ghci>:t (F.toFrame $ map createRecId res1)
   (F.toFrame $ map createRecId res1)
     :: F.Frame
         (F.Record
             '["_cart_usersEmail" F.:-> Text,
               "_cart_usersFirst_name" F.:-> Text,
               "_cart_usersLast_name" F.:-> Text,
               "_cart_usersIs_member" F.:-> Bool,
               "_cart_usersDays_in_queue" F.:-> Int])
   ghci>myFrame = F.toFrame $ map createRecId res1
   ghci>:set -XTypeApplications
   ghci>:set -XTypeOperators
   ghci>:set -XDataKinds
   ghci>miniFrame = fmap (F.rcast '["_cart_usersEmail" F.:-> Text, "_cart_usersDays_in_queue" F.:-> Int]) myFrame
   ghci>mapM_ print miniFrame
   {_cart_usersEmail :-> "jamesexample.com", _cart_usersDays_in_queue :-> 1}
   {_cart_usersEmail :-> "bettyexample.com", _cart_usersDays_in_queue :-> 42}
   {_cart_usersEmail :-> "jamespallo.com", _cart_usersDays_in_queue :-> 1}
   {_cart_usersEmail :-> "bettysims.com", _cart_usersDays_in_queue :-> 42}
   {_cart_usersEmail :-> "jamesoreily.com", _cart_usersDays_in_queue :-> 1}
   

We could have used loadRows2 in place of loadRows1 in order to have the WHERE ... clause executed at the DB-level. Note that in the above, once the query results are converted to a data frame, you're free to play with the frame in anyway, just like you would for a data frame created from a CSV.

B. Streaming Workflow Steps

Once you're done working with a small subset of data, and would like to scale up your analysis by looking at a larger-subset-of/complete data, then it's time to look at writing your own conduit to process incoming rows from the DB.

1 - 4: Same as 'Interactive Workflow Steps'

5. Writing your own streaming pipeline: Consider the following:

   streamRows :: IO ()
   streamRows = do
     res <-  withConnection connString $
               streamingSelectAllPipeline' _cart_users db 1000 (c -> (_cart_usersFirst_name c) `like_` "J%") $
                 (CL.map (record -> F.rcast @["_cart_usersEmail" F.:-> Text, "_cart_usersIs_member" F.:-> Bool] record))
     mapM_ print res
   

In the above, we select all rows from the specified table that match a certain pattern ("J%"), then the function streamingSelectAllPipeline' converts the query results to vinyl records inside a conduit and sends it downstream, where we can operate on its output. Here, specifically, we do a column subset of the output using rcast, and CL.map applies rcast to every incoming row and sends it downstream, where the result gets returned. We then print the list of vinyl records.

In order to write your own conduit, all you need to know is that internally the conduit flow is as follows:

   (c -> runConduit $ c .| CL.map createRecId
                         .| recordProcessorConduit
                         .| CL.take nrows)
   

In the above, you supply the recordProcessorConduit to the streamingSelectAllPipeline' function which takes a vinyl record as input and sends it downstream to the CL.take. Note that in all functions in the Frames.SQL.Beam.Postgres.Streaming module, you need to specify the number of rows you want to return (this is an upper bound of sorts, the actual number of rows returned depends on the amount of data present in your database).

A Note on 'Filter Lambdas'

A Note on 'Canned Queries' and 'Filter Lambdas':

There are three things needed to execute a canned query ('SELECT * FROM tbl WHERE ...'):

  • PostgresTable a b: auto generated by BeamSchemaGen module
  • PostgresDB b: auto generated by BeamSchemaGen module
  • PostgresFilterLambda a s: The WHERE... clause. All filter lambdas are of the form:
   (tbl -> (_fieldName tbl) op constant)
   

or

   (tbl -> (_fieldName1 tbl) op (_fieldName2 tbl))
   

In the above op can be one of : [==., /=., >., <., <=., >=., between_, like_, in_ ] (some of these are not be applicable to the second case). You may use &&. and ||. to combine expressions inside the lambda. To see some actual examples of 'filter lambdas', check out test/LibSpec.hs in this repository.

Re-exports of the underlying modules

Re-exports of beam-core and beam-postgres

Postgres Column Types

data ByteString :: * #

A space-efficient representation of a Word8 vector, supporting many efficient operations.

A ByteString contains 8-bit bytes, or by using the operations from Data.ByteString.Char8 it can be interpreted as containing 8-bit characters.

Instances

Eq ByteString 
Data ByteString 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ByteString -> c ByteString #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ByteString #

toConstr :: ByteString -> Constr #

dataTypeOf :: ByteString -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ByteString) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ByteString) #

gmapT :: (forall b. Data b => b -> b) -> ByteString -> ByteString #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ByteString -> r #

gmapQ :: (forall d. Data d => d -> u) -> ByteString -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ByteString -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ByteString -> m ByteString #

Ord ByteString 
Read ByteString 
Show ByteString 
IsString ByteString 
Semigroup ByteString 
Monoid ByteString 
Chunk ByteString 
FoldCase ByteString

Note that foldCase on ByteStrings is only guaranteed to be correct for ISO-8859-1 encoded strings!

NFData ByteString 

Methods

rnf :: ByteString -> () #

ToHStoreText ByteString

Assumed to be UTF-8 encoded

FromField ByteString

bytea, name, text, "char", bpchar, varchar, unknown

HasSqlEqualityCheck PgExpressionSyntax ByteString 
HasSqlQuantifiedEqualityCheck PgExpressionSyntax ByteString 
HasSqlValueSyntax Value ByteString 
HasSqlValueSyntax PgValueSyntax ByteString 
FromBackendRow Postgres ByteString 
HasDefaultSqlDataTypeConstraints PgColumnSchemaSyntax ByteString 
HasDefaultSqlDataType PgDataTypeSyntax ByteString 
FromBackendRow Postgres (Binary ByteString) 
FromField (Binary ByteString)

bytea

type State ByteString 
type State ByteString = Buffer
type ChunkElem ByteString 

data Text :: * #

A space efficient, packed, unboxed Unicode text type.

Instances

FromJSON Text 
FromJSONKey Text 
Chunk Text 
FoldCase Text 

Methods

foldCase :: Text -> Text #

foldCaseList :: [Text] -> [Text]

ToHStoreText Text 
FromField Text

name, text, "char", bpchar, varchar

HasSqlEqualityCheck PgExpressionSyntax Text 
HasSqlQuantifiedEqualityCheck PgExpressionSyntax Text 
HasSqlValueSyntax SqlSyntaxBuilder Text 
HasSqlValueSyntax Value Text 

Methods

sqlValueSyntax :: Text -> Value #

HasSqlValueSyntax PgValueSyntax Text 
FromBackendRow Postgres Text 
Beamable t => ProjectibleWithPredicate AnyType Text (t (QField s)) 

Methods

project' :: Monad m => Proxy (* -> Constraint) AnyType -> (forall context. AnyType context => Proxy * context -> WithExprContext Text -> m (WithExprContext Text)) -> t (QField s) -> m (t (QField s)) #

Beamable t => ProjectibleWithPredicate AnyType Text (t (Nullable (QField s))) 

Methods

project' :: Monad m => Proxy (* -> Constraint) AnyType -> (forall context. AnyType context => Proxy * context -> WithExprContext Text -> m (WithExprContext Text)) -> t (Nullable (QField s)) -> m (t (Nullable (QField s))) #

ProjectibleWithPredicate AnyType Text (QField s a) 

Methods

project' :: Monad m => Proxy (* -> Constraint) AnyType -> (forall context. AnyType context => Proxy * context -> WithExprContext Text -> m (WithExprContext Text)) -> QField s a -> m (QField s a) #

HasSqlEqualityCheck PgExpressionSyntax (CI Text) 
HasSqlQuantifiedEqualityCheck PgExpressionSyntax (CI Text) 
HasSqlValueSyntax PgValueSyntax (CI Text) 
FromBackendRow Postgres (CI Text) 
FromField (CI Text)

citext

IsSqlExpressionSyntaxStringType * * SqlSyntaxBuilder Text 
IsSqlExpressionSyntaxStringType * * Expression Text 
IsSqlExpressionSyntaxStringType * * PgExpressionSyntax Text 
(IsSql92ExpressionSyntax syntax, HasSqlValueSyntax (Sql92ExpressionValueSyntax syntax) [Char]) => IsString (QGenExpr context syntax s Text) 

Methods

fromString :: String -> QGenExpr context syntax s Text #

type VectorFor Text 
type State Text 
type State Text = Buffer
type ChunkElem Text 
type Item Text 
type Item Text = Char

data UUID :: * #

The UUID type. A Random instance is provided which produces version 4 UUIDs as specified in RFC 4122. The Storable and Binary instances are compatible with RFC 4122, storing the fields in network order as 16 bytes.

Instances

Eq UUID 

Methods

(==) :: UUID -> UUID -> Bool #

(/=) :: UUID -> UUID -> Bool #

Data UUID 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UUID -> c UUID #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UUID #

toConstr :: UUID -> Constr #

dataTypeOf :: UUID -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UUID) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UUID) #

gmapT :: (forall b. Data b => b -> b) -> UUID -> UUID #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UUID -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UUID -> r #

gmapQ :: (forall d. Data d => d -> u) -> UUID -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UUID -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UUID -> m UUID #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UUID -> m UUID #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UUID -> m UUID #

Ord UUID 

Methods

compare :: UUID -> UUID -> Ordering #

(<) :: UUID -> UUID -> Bool #

(<=) :: UUID -> UUID -> Bool #

(>) :: UUID -> UUID -> Bool #

(>=) :: UUID -> UUID -> Bool #

max :: UUID -> UUID -> UUID #

min :: UUID -> UUID -> UUID #

Read UUID 
Show UUID 

Methods

showsPrec :: Int -> UUID -> ShowS #

show :: UUID -> String #

showList :: [UUID] -> ShowS #

Hashable UUID 

Methods

hashWithSalt :: Int -> UUID -> Int #

hash :: UUID -> Int #

FromJSON UUID 
FromJSONKey UUID 
Storable UUID 

Methods

sizeOf :: UUID -> Int #

alignment :: UUID -> Int #

peekElemOff :: Ptr UUID -> Int -> IO UUID #

pokeElemOff :: Ptr UUID -> Int -> UUID -> IO () #

peekByteOff :: Ptr b -> Int -> IO UUID #

pokeByteOff :: Ptr b -> Int -> UUID -> IO () #

peek :: Ptr UUID -> IO UUID #

poke :: Ptr UUID -> UUID -> IO () #

Binary UUID 

Methods

put :: UUID -> Put #

get :: Get UUID #

putList :: [UUID] -> Put #

NFData UUID 

Methods

rnf :: UUID -> () #

FromField UUID

uuid

Random UUID 

Methods

randomR :: RandomGen g => (UUID, UUID) -> g -> (UUID, g) #

random :: RandomGen g => g -> (UUID, g) #

randomRs :: RandomGen g => (UUID, UUID) -> g -> [UUID] #

randoms :: RandomGen g => g -> [UUID] #

randomRIO :: (UUID, UUID) -> IO UUID #

randomIO :: IO UUID #

HasSqlEqualityCheck PgExpressionSyntax UUID 
HasSqlQuantifiedEqualityCheck PgExpressionSyntax UUID 
HasSqlValueSyntax PgValueSyntax UUID 
FromBackendRow Postgres UUID 
HasDefaultSqlDataTypeConstraints PgColumnSchemaSyntax UUID 
HasDefaultSqlDataType PgDataTypeSyntax UUID 

data Scientific :: * #

An arbitrary-precision number represented using scientific notation.

This type describes the set of all Reals which have a finite decimal expansion.

A scientific number with coefficient c and base10Exponent e corresponds to the Fractional number: fromInteger c * 10 ^^ e

Instances

Eq Scientific 
Fractional Scientific

WARNING: recip and / will diverge (i.e. loop and consume all space) when their outputs are repeating decimals.

fromRational will diverge when the input Rational is a repeating decimal. Consider using fromRationalRepetend for these rationals which will detect the repetition and indicate where it starts.

Data Scientific 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Scientific -> c Scientific #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Scientific #

toConstr :: Scientific -> Constr #

dataTypeOf :: Scientific -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Scientific) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Scientific) #

gmapT :: (forall b. Data b => b -> b) -> Scientific -> Scientific #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Scientific -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Scientific -> r #

gmapQ :: (forall d. Data d => d -> u) -> Scientific -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Scientific -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Scientific -> m Scientific #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Scientific -> m Scientific #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Scientific -> m Scientific #

Num Scientific 
Ord Scientific 
Read Scientific

Supports the skipping of parentheses and whitespaces. Example:

> read " ( ((  -1.0e+3 ) ))" :: Scientific
-1000.0

(Note: This Read instance makes internal use of scientificP to parse the floating-point number.)

Real Scientific

WARNING: toRational needs to compute the Integer magnitude: 10^e. If applied to a huge exponent this could fill up all space and crash your program!

Avoid applying toRational (or realToFrac) to scientific numbers coming from an untrusted source and use toRealFloat instead. The latter guards against excessive space usage.

RealFrac Scientific 
Show Scientific 
Hashable Scientific 
FromJSON Scientific 
Binary Scientific 
NFData Scientific 

Methods

rnf :: Scientific -> () #

FromField Scientific

int2, int4, int8, float4, float8, numeric

HasSqlEqualityCheck PgExpressionSyntax Scientific 
HasSqlQuantifiedEqualityCheck PgExpressionSyntax Scientific 
HasSqlValueSyntax PgValueSyntax Scientific 
FromBackendRow Postgres Scientific 
ToField (PGRange Scientific) 

data UTCTime :: * #

This is the simplest representation of UTC. It consists of the day number, and a time offset from midnight. Note that if a day has a leap second added to it, it will have 86401 seconds.

Instances

Eq UTCTime 

Methods

(==) :: UTCTime -> UTCTime -> Bool #

(/=) :: UTCTime -> UTCTime -> Bool #

Data UTCTime 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> UTCTime -> c UTCTime #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c UTCTime #

toConstr :: UTCTime -> Constr #

dataTypeOf :: UTCTime -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c UTCTime) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c UTCTime) #

gmapT :: (forall b. Data b => b -> b) -> UTCTime -> UTCTime #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> UTCTime -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> UTCTime -> r #

gmapQ :: (forall d. Data d => d -> u) -> UTCTime -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> UTCTime -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> UTCTime -> m UTCTime #

Ord UTCTime 
FromJSON UTCTime 
FromJSONKey UTCTime 
NFData UTCTime 

Methods

rnf :: UTCTime -> () #

FromField UTCTime

timestamptz

FromField UTCTimestamp

timestamptz

ParseTime UTCTime 
HasSqlEqualityCheck PgExpressionSyntax UTCTime 
HasSqlEqualityCheck PgExpressionSyntax UTCTimestamp 
HasSqlQuantifiedEqualityCheck PgExpressionSyntax UTCTime 
HasSqlQuantifiedEqualityCheck PgExpressionSyntax UTCTimestamp 
HasSqlValueSyntax Value UTCTime 
HasSqlValueSyntax PgValueSyntax UTCTime 
HasSqlValueSyntax PgValueSyntax UTCTimestamp 
FromBackendRow Postgres UTCTime 
FromBackendRow Postgres UTCTimestamp 
ToField (PGRange UTCTime) 
ToField (PGRange UTCTimestamp) 

data LocalTime :: * #

A simple day and time aggregate, where the day is of the specified parameter, and the time is a TimeOfDay. Conversion of this (as local civil time) to UTC depends on the time zone. Conversion of this (as local mean time) to UT1 depends on the longitude.

Instances

Eq LocalTime 
Data LocalTime 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LocalTime -> c LocalTime #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LocalTime #

toConstr :: LocalTime -> Constr #

dataTypeOf :: LocalTime -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c LocalTime) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LocalTime) #

gmapT :: (forall b. Data b => b -> b) -> LocalTime -> LocalTime #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LocalTime -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LocalTime -> r #

gmapQ :: (forall d. Data d => d -> u) -> LocalTime -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LocalTime -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LocalTime -> m LocalTime #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LocalTime -> m LocalTime #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LocalTime -> m LocalTime #

Ord LocalTime 
Show LocalTime 
FromJSON LocalTime 
FromJSONKey LocalTime 
NFData LocalTime 

Methods

rnf :: LocalTime -> () #

FromField LocalTimestamp

timestamp

FromField LocalTime

timestamp

ParseTime LocalTime 
HasSqlEqualityCheck PgExpressionSyntax LocalTimestamp 
HasSqlEqualityCheck PgExpressionSyntax LocalTime 
HasSqlQuantifiedEqualityCheck PgExpressionSyntax LocalTimestamp 
HasSqlQuantifiedEqualityCheck PgExpressionSyntax LocalTime 
HasSqlValueSyntax Value LocalTime 
HasSqlValueSyntax PgValueSyntax LocalTimestamp 
HasSqlValueSyntax PgValueSyntax LocalTime 
FromBackendRow Postgres LocalTimestamp 
FromBackendRow Postgres LocalTime 
HasDefaultSqlDataTypeConstraints PgColumnSchemaSyntax LocalTime 
HasDefaultSqlDataType PgDataTypeSyntax LocalTime 
ToField (PGRange LocalTimestamp) 
ToField (PGRange LocalTime) 

data TimeOfDay :: * #

Time of day as represented in hour, minute and second (with picoseconds), typically used to express local time of day.

Instances

Eq TimeOfDay 
Data TimeOfDay 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> TimeOfDay -> c TimeOfDay #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c TimeOfDay #

toConstr :: TimeOfDay -> Constr #

dataTypeOf :: TimeOfDay -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c TimeOfDay) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c TimeOfDay) #

gmapT :: (forall b. Data b => b -> b) -> TimeOfDay -> TimeOfDay #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> TimeOfDay -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> TimeOfDay -> r #

gmapQ :: (forall d. Data d => d -> u) -> TimeOfDay -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> TimeOfDay -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> TimeOfDay -> m TimeOfDay #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeOfDay -> m TimeOfDay #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> TimeOfDay -> m TimeOfDay #

Ord TimeOfDay 
Show TimeOfDay 
FromJSON TimeOfDay 
FromJSONKey TimeOfDay 
NFData TimeOfDay 

Methods

rnf :: TimeOfDay -> () #

FromField TimeOfDay

time

ParseTime TimeOfDay 
HasSqlEqualityCheck PgExpressionSyntax TimeOfDay 
HasSqlQuantifiedEqualityCheck PgExpressionSyntax TimeOfDay 
HasSqlValueSyntax Value TimeOfDay 
HasSqlValueSyntax PgValueSyntax TimeOfDay 
FromBackendRow Postgres TimeOfDay 
ToField (PGRange TimeOfDay) 

data Day :: * #

The Modified Julian Day is a standard count of days, with zero being the day 1858-11-17.

Instances

Enum Day 

Methods

succ :: Day -> Day #

pred :: Day -> Day #

toEnum :: Int -> Day #

fromEnum :: Day -> Int #

enumFrom :: Day -> [Day] #

enumFromThen :: Day -> Day -> [Day] #

enumFromTo :: Day -> Day -> [Day] #

enumFromThenTo :: Day -> Day -> Day -> [Day] #

Eq Day 

Methods

(==) :: Day -> Day -> Bool #

(/=) :: Day -> Day -> Bool #

Data Day 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Day -> c Day #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Day #

toConstr :: Day -> Constr #

dataTypeOf :: Day -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Day) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Day) #

gmapT :: (forall b. Data b => b -> b) -> Day -> Day #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Day -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Day -> r #

gmapQ :: (forall d. Data d => d -> u) -> Day -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Day -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Day -> m Day #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Day -> m Day #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Day -> m Day #

Ord Day 

Methods

compare :: Day -> Day -> Ordering #

(<) :: Day -> Day -> Bool #

(<=) :: Day -> Day -> Bool #

(>) :: Day -> Day -> Bool #

(>=) :: Day -> Day -> Bool #

max :: Day -> Day -> Day #

min :: Day -> Day -> Day #

Ix Day 

Methods

range :: (Day, Day) -> [Day] #

index :: (Day, Day) -> Day -> Int #

unsafeIndex :: (Day, Day) -> Day -> Int

inRange :: (Day, Day) -> Day -> Bool #

rangeSize :: (Day, Day) -> Int #

unsafeRangeSize :: (Day, Day) -> Int

FromJSON Day 
FromJSONKey Day 
NFData Day 

Methods

rnf :: Day -> () #

FromField Date

date

FromField Day

date

ParseTime Day 

Methods

buildTime :: TimeLocale -> [(Char, String)] -> Maybe Day #

HasSqlEqualityCheck PgExpressionSyntax Date 
HasSqlEqualityCheck PgExpressionSyntax Day 
HasSqlQuantifiedEqualityCheck PgExpressionSyntax Date 
HasSqlQuantifiedEqualityCheck PgExpressionSyntax Day 
HasSqlValueSyntax Value Day 

Methods

sqlValueSyntax :: Day -> Value #

HasSqlValueSyntax PgValueSyntax Date 
HasSqlValueSyntax PgValueSyntax Day 
FromBackendRow Postgres Date 
FromBackendRow Postgres Day 
ToField (PGRange Date) 

Methods

toField :: PGRange Date -> Action #

ToField (PGRange Day) 

Methods

toField :: PGRange Day -> Action #

Re-exports for the deriveGeneric plus deriveVinyl combination

deriveGeneric :: Name -> Q [Dec] #

Generate generics-sop boilerplate for the given datatype.

This function takes the name of a datatype and generates:

Note that the generated code will require the TypeFamilies and DataKinds extensions to be enabled for the module.

Example: If you have the datatype

data Tree = Leaf Int | Node Tree Tree

and say

deriveGeneric ''Tree

then you get code that is equivalent to:

instance Generic Tree where

  type Code Tree = '[ '[Int], '[Tree, Tree] ]

  from (Leaf x)   = SOP (   Z (I x :* Nil))
  from (Node l r) = SOP (S (Z (I l :* I r :* Nil)))

  to (SOP    (Z (I x :* Nil)))         = Leaf x
  to (SOP (S (Z (I l :* I r :* Nil)))) = Node l r
  to _ = error "unreachable" -- to avoid GHC warnings

instance HasDatatypeInfo Tree where
  type DatatypeInfoOf Tree =
    T.ADT "Main" "Tree"
      '[ T.Constructor "Leaf", T.Constructor "Node" ]

  datatypeInfo _ =
    T.demoteDatatypeInfo (Proxy :: Proxy (DatatypeInfoOf Tree))

Limitations: Generation does not work for GADTs, for datatypes that involve existential quantification, for datatypes with unboxed fields.