| Copyright | (c) Gagandeep Bhatia 2018 | 
|---|---|
| License | BSD3 | 
| Stability | experimental | 
| Safe Haskell | None | 
| Language | Haskell2010 | 
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
- module Frames.SQL.Beam.Postgres.Vinylize
- module Frames.SQL.Beam.Postgres.BeamSchemaGen
- module Frames.SQL.Beam.Postgres.Query
- module Frames.SQL.Beam.Postgres.Streaming
- module Database.Beam
- module Database.Beam.Postgres
- data ByteString
- data Text
- data UUID
- data Scientific
- data UTCTime
- type LocalTimestamp = Unbounded LocalTime
- type UTCTimestamp = Unbounded UTCTime
- type ZonedTimestamp = Unbounded ZonedTime
- data LocalTime
- data TimeOfDay
- type Date = Unbounded Day
- data Day
- module Data.Coerce
- data Proxy (t :: k) :: forall k. k -> * = Proxy
- data Associativity
- type Rep a = SOP I (Code a)
- type family Code a :: [[*]]
- from :: Generic a => a -> Rep a
- to :: Generic a => Rep a -> a
- class HasDatatypeInfo a where- type DatatypeInfoOf a :: DatatypeInfo
 
- type IsProductType a (xs :: [*]) = (Generic a, Code a ~ (xs ': ([] :: [[*]])))
- type IsEnumType a = (Generic a, All ([*] ~ ([] :: [*])) (Code a))
- type IsWrappedType a x = (Generic a, Code a ~ ((x ': ([] :: [*])) ': ([] :: [[*]])))
- type IsNewtype a x = (IsWrappedType a x, Coercible a x)
- constructorName :: ConstructorInfo xs -> ConstructorName
- constructorInfo :: DatatypeInfo xss -> NP ConstructorInfo xss
- datatypeName :: DatatypeInfo xss -> DatatypeName
- moduleName :: DatatypeInfo xss -> ModuleName
- data DatatypeInfo (a :: [[*]]) where- ADT :: DatatypeInfo a
- Newtype :: DatatypeInfo ((x ': ([] :: [*])) ': ([] :: [[*]]))
 
- data ConstructorInfo (a :: [*]) where- Constructor :: ConstructorInfo a
- Infix :: ConstructorInfo (x ': (y ': ([] :: [*])))
- Record :: ConstructorInfo a
 
- data FieldInfo a = FieldInfo FieldName
- type DatatypeName = String
- type ModuleName = String
- type ConstructorName = String
- type FieldName = String
- type Fixity = Int
- ccompare_SOP :: All2 c xss => proxy c -> r -> (forall (xs :: [k]). All c xs => NP f xs -> NP g xs -> r) -> r -> SOP f xss -> SOP g xss -> r
- compare_SOP :: r -> (forall (xs :: [k]). NP f xs -> NP g xs -> r) -> r -> SOP f xss -> SOP g xss -> r
- ccompare_NS :: All c xs => proxy c -> r -> (forall (x :: k). c x => f x -> g x -> r) -> r -> NS f xs -> NS g xs -> r
- compare_NS :: r -> (forall (x :: k). f x -> g x -> r) -> r -> NS f xs -> NS g xs -> r
- apInjs_POP :: SListI xss => POP f xss -> [SOP f xss]
- apInjs_NP :: SListI xs => NP f xs -> [NS f xs]
- shift :: Injection f xs a2 -> Injection f (x ': xs) a2
- shiftInjection :: Injection f xs a2 -> Injection f (x ': xs) a2
- injections :: SListI xs => NP (Injection f xs) xs
- unSOP :: SOP f xss -> NS (NP f) xss
- unZ :: NS f (x ': ([] :: [k])) -> f x
- data NS (a :: k -> *) (b :: [k]) :: forall k. (k -> *) -> [k] -> * where
- newtype SOP (f :: k -> *) (xss :: [[k]]) :: forall k. (k -> *) -> [[k]] -> * = SOP (NS (NP f) xss)
- type Injection (f :: k -> *) (xs :: [k]) = f -.-> (K (NS f xs) :: k -> *)
- hcliftA3' :: (All2 c xss, Prod h ~ (NP :: ([k] -> *) -> [[k]] -> *), HAp h) => proxy c -> (forall (xs :: [k]). All c xs => f xs -> f' xs -> f'' xs -> f''' xs) -> Prod h f xss -> Prod h f' xss -> h f'' xss -> h f''' xss
- hcliftA2' :: (All2 c xss, Prod h ~ (NP :: ([k] -> *) -> [[k]] -> *), HAp h) => proxy c -> (forall (xs :: [k]). All c xs => f xs -> f' xs -> f'' xs) -> Prod h f xss -> h f' xss -> h f'' xss
- hcliftA' :: (All2 c xss, Prod h ~ (NP :: ([k] -> *) -> [[k]] -> *), HAp h) => proxy c -> (forall (xs :: [k]). All c xs => f xs -> f' xs) -> h f xss -> h f' xss
- shiftProjection :: Projection f xs a2 -> Projection f (x ': xs) a2
- projections :: SListI xs => NP (Projection f xs) xs
- tl :: NP f (x ': xs) -> NP f xs
- hd :: NP f (x ': xs) -> f x
- fromList :: SListI xs => [a] -> Maybe (NP (K a :: k -> *) xs)
- unPOP :: POP f xss -> NP (NP f) xss
- data NP (a :: k -> *) (b :: [k]) :: forall k. (k -> *) -> [k] -> * where
- newtype POP (f :: k -> *) (xss :: [[k]]) :: forall k. (k -> *) -> [[k]] -> * = POP (NP (NP f) xss)
- type Projection (f :: k -> *) (xs :: [k]) = (K (NP f xs) :: k -> *) -.-> f
- htoI :: (AllZipN (Prod h1) (LiftedCoercible f I) xs ys, HTrans h1 h2) => h1 f xs -> h2 I ys
- hfromI :: (AllZipN (Prod h1) (LiftedCoercible I f) xs ys, HTrans h1 h2) => h1 I xs -> h2 f ys
- hsequenceK :: (SListIN h xs, SListIN (Prod h) xs, Applicative f, HSequence h) => h (K (f a) :: k -> *) xs -> f (h (K a :: k -> *) xs)
- hsequence :: (SListIN h xs, SListIN (Prod h) xs, HSequence h, Applicative f) => h f xs -> f (h I xs)
- hcfor :: (HSequence h, AllN h c xs, Applicative g) => proxy c -> h f xs -> (forall a. c a => f a -> g a) -> g (h I xs)
- hctraverse :: (HSequence h, AllN h c xs, Applicative g) => proxy c -> (forall a. c a => f a -> g a) -> h f xs -> g (h I xs)
- hcfoldMap :: (HTraverse_ h, AllN h c xs, Monoid m) => proxy c -> (forall (a :: k). c a => f a -> m) -> h f xs -> m
- hcfor_ :: (HTraverse_ h, AllN h c xs, Applicative g) => proxy c -> h f xs -> (forall (a :: k). c a => f a -> g ()) -> g ()
- hczipWith3 :: (AllN (Prod h) c xs, HAp h, HAp (Prod h)) => proxy c -> (forall (a :: k). c a => f a -> f' a -> f'' a -> f''' a) -> Prod h f xs -> Prod h f' xs -> h f'' xs -> h f''' xs
- hczipWith :: (AllN (Prod h) c xs, HAp h, HAp (Prod h)) => proxy c -> (forall (a :: k). c a => f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs
- hcmap :: (AllN (Prod h) c xs, HAp h) => proxy c -> (forall (a :: k). c a => f a -> f' a) -> h f xs -> h f' xs
- hcliftA3 :: (AllN (Prod h) c xs, HAp h, HAp (Prod h)) => proxy c -> (forall (a :: k). c a => f a -> f' a -> f'' a -> f''' a) -> Prod h f xs -> Prod h f' xs -> h f'' xs -> h f''' xs
- hcliftA2 :: (AllN (Prod h) c xs, HAp h, HAp (Prod h)) => proxy c -> (forall (a :: k). c a => f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs
- hcliftA :: (AllN (Prod h) c xs, HAp h) => proxy c -> (forall (a :: k). c a => f a -> f' a) -> h f xs -> h f' xs
- hzipWith3 :: (SListIN (Prod h) xs, HAp h, HAp (Prod h)) => (forall (a :: k). f a -> f' a -> f'' a -> f''' a) -> Prod h f xs -> Prod h f' xs -> h f'' xs -> h f''' xs
- hzipWith :: (SListIN (Prod h) xs, HAp h, HAp (Prod h)) => (forall (a :: k). f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs
- hmap :: (SListIN (Prod h) xs, HAp h) => (forall (a :: k). f a -> f' a) -> h f xs -> h f' xs
- hliftA3 :: (SListIN (Prod h) xs, HAp h, HAp (Prod h)) => (forall (a :: k). f a -> f' a -> f'' a -> f''' a) -> Prod h f xs -> Prod h f' xs -> h f'' xs -> h f''' xs
- hliftA2 :: (SListIN (Prod h) xs, HAp h, HAp (Prod h)) => (forall (a :: k). f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs
- hliftA :: (SListIN (Prod h) xs, HAp h) => (forall (a :: k). f a -> f' a) -> h f xs -> h f' xs
- fn_4 :: (f a -> f' a -> f'' a -> f''' a -> f'''' a) -> (f -.-> (f' -.-> (f'' -.-> (f''' -.-> f'''')))) a
- fn_3 :: (f a -> f' a -> f'' a -> f''' a) -> (f -.-> (f' -.-> (f'' -.-> f'''))) a
- fn_2 :: (f a -> f' a -> f'' a) -> (f -.-> (f' -.-> f'')) a
- fn :: (f a -> f' a) -> (f -.-> f') a
- class HPure (h :: (k -> *) -> l -> *) where
- newtype ((f :: k -> *) -.-> (g :: k -> *)) (a :: k) :: forall k. (k -> *) -> (k -> *) -> k -> * = Fn {- apFn :: f a -> g a
 
- type family Prod (h :: (k -> *) -> l -> *) :: (k -> *) -> l -> *
- class (Prod (Prod h) ~ Prod h, HPure (Prod h)) => HAp (h :: (k -> *) -> l -> *) where
- type family CollapseTo (h :: (k -> *) -> l -> *) x :: *
- class HCollapse (h :: (k -> *) -> l -> *) where
- class HTraverse_ (h :: (k -> *) -> l -> *) where
- class HAp h => HSequence (h :: (k -> *) -> l -> *) where
- class HIndex (h :: (k -> *) -> l -> *) where
- type family UnProd (h :: (k -> *) -> l -> *) :: (k -> *) -> l -> *
- class UnProd (Prod h) ~ h => HApInjs (h :: (k -> *) -> l -> *) where
- class HExpand (h :: (k -> *) -> l -> *) where
- class ((Same h1 :: (k2 -> *) -> l2 -> *) ~ h2, (Same h2 :: (k1 -> *) -> l1 -> *) ~ h1) => HTrans (h1 :: (k1 -> *) -> l1 -> *) (h2 :: (k2 -> *) -> l2 -> *) where
- class (AllF f xs, SListI xs) => All (f :: k -> Constraint) (xs :: [k])
- type SListI2 = All (SListI :: [k] -> Constraint)
- class (AllF (All f) xss, SListI xss) => All2 (f :: k -> Constraint) (xss :: [[k]])
- class (SListI xs, SListI ys, SameShapeAs xs ys, SameShapeAs ys xs, AllZipF c xs ys) => AllZip (c :: a -> b -> Constraint) (xs :: [a]) (ys :: [b])
- type family SameShapeAs (xs :: [a]) (ys :: [b]) :: Constraint where ...
- class Coercible (f x) (g y) => LiftedCoercible (f :: k -> k0) (g :: k1 -> k0) (x :: k) (y :: k1)
- class (AllZipF (AllZip f) xss yss, SListI xss, SListI yss, SameShapeAs xss yss, SameShapeAs yss xss) => AllZip2 (f :: a -> b -> Constraint) (xss :: [[a]]) (yss :: [[b]])
- class f (g x) => Compose (f :: k -> Constraint) (g :: k1 -> k) (x :: k1)
- class (f x, g x) => And (f :: k -> Constraint) (g :: k -> Constraint) (x :: k)
- class Top (x :: k)
- type family AllN (h :: (k -> *) -> l -> *) (c :: k -> Constraint) :: l -> Constraint
- type family AllZipN (h :: (k -> *) -> l -> *) (c :: k1 -> k2 -> Constraint) :: l1 -> l2 -> Constraint
- lengthSing :: SListI xs => proxy xs -> Int
- lengthSList :: SListI xs => proxy xs -> Int
- shape :: SListI xs => Shape xs
- data SList (a :: [k]) :: forall k. [k] -> * where
- class SListI (xs :: [k]) where
- class SListI xs => SingI (xs :: [k]) where
- type Sing = (SList :: [k] -> *)
- data Shape (a :: [k]) :: forall k. [k] -> * where
- mapKKK :: (a -> b -> c) -> K a d -> K b e -> K c f
- mapKKI :: (a -> b -> c) -> K a d -> K b e -> I c
- mapKIK :: (a -> b -> c) -> K a d -> I b -> K c e
- mapKII :: (a -> b -> c) -> K a d -> I b -> I c
- mapIKK :: (a -> b -> c) -> I a -> K b d -> K c e
- mapIKI :: (a -> b -> c) -> I a -> K b d -> I c
- mapIIK :: (a -> b -> c) -> I a -> I b -> K c d
- mapIII :: (a -> b -> c) -> I a -> I b -> I c
- mapKK :: (a -> b) -> K a c -> K b d
- mapKI :: (a -> b) -> K a c -> I b
- mapIK :: (a -> b) -> I a -> K b c
- mapII :: (a -> b) -> I a -> I b
- unComp :: (f :.: g) p -> f (g p)
- unI :: I a -> a
- unK :: K a b -> a
- newtype K a (b :: k) :: forall k. * -> k -> * = K a
- newtype I a = I a
- newtype ((f :: l -> *) :.: (g :: k -> l)) (p :: k) :: forall l k. (l -> *) -> (k -> l) -> k -> * = Comp (f (g p))
- deriveGeneric :: Name -> Q [Dec]
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_usersTderiveVinyl''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" -- selectsnrows from the specified table in the db. loadRows1 :: Int -> IO [(Cart_usersT Identity)] loadRows1 n =withConnectionconnString $bulkSelectAllRows_cart_users db n loadRows2 :: Int -> IO [(Cart_usersT Identity)] loadRows2 n =withConnectionconnString $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
module Database.Beam
module Database.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
A space efficient, packed, unboxed Unicode text type.
Instances
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
data Scientific #
An arbitrary-precision number represented using scientific notation.
This type describes the set of all Reals
A scientific number with coefficient c and base10Exponent e
 corresponds to the Fractional number: fromInteger c * 10 ^^ e
Instances
| Eq Scientific | Scientific numbers can be safely compared for equality. No magnitude  | 
| Defined in Data.Scientific | |
| Fractional Scientific | WARNING:  
 | 
| Defined in Data.Scientific Methods (/) :: Scientific -> Scientific -> Scientific # recip :: Scientific -> Scientific # fromRational :: Rational -> Scientific # | |
| Data Scientific | |
| Defined in 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 | WARNING:  | 
| Defined in Data.Scientific Methods (+) :: Scientific -> Scientific -> Scientific # (-) :: Scientific -> Scientific -> Scientific # (*) :: Scientific -> Scientific -> Scientific # negate :: Scientific -> Scientific # abs :: Scientific -> Scientific # signum :: Scientific -> Scientific # fromInteger :: Integer -> Scientific # | |
| Ord Scientific | Scientific numbers can be safely compared for ordering. No magnitude  | 
| Defined in Data.Scientific Methods compare :: Scientific -> Scientific -> Ordering # (<) :: Scientific -> Scientific -> Bool # (<=) :: Scientific -> Scientific -> Bool # (>) :: Scientific -> Scientific -> Bool # (>=) :: Scientific -> Scientific -> Bool # max :: Scientific -> Scientific -> Scientific # min :: Scientific -> Scientific -> Scientific # | |
| Read Scientific | Supports the skipping of parentheses and whitespaces. Example: > read " ( (( -1.0e+3 ) ))" :: Scientific -1000.0 (Note: This  | 
| Defined in Data.Scientific Methods readsPrec :: Int -> ReadS Scientific # readList :: ReadS [Scientific] # readPrec :: ReadPrec Scientific # readListPrec :: ReadPrec [Scientific] # | |
| Real Scientific | WARNING:  Avoid applying  | 
| Defined in Data.Scientific Methods toRational :: Scientific -> Rational # | |
| RealFrac Scientific | WARNING: the methods of the  | 
| Defined in Data.Scientific Methods properFraction :: Integral b => Scientific -> (b, Scientific) # truncate :: Integral b => Scientific -> b # round :: Integral b => Scientific -> b # ceiling :: Integral b => Scientific -> b # floor :: Integral b => Scientific -> b # | |
| Show Scientific | See  | 
| Defined in Data.Scientific Methods showsPrec :: Int -> Scientific -> ShowS # show :: Scientific -> String # showList :: [Scientific] -> ShowS # | |
| Hashable Scientific | A hash can be safely calculated from a  | 
| Defined in Data.Scientific | |
| FromJSON Scientific | |
| Defined in Data.Aeson.Types.FromJSON | |
| Binary Scientific | Note that in the future I intend to change the type of the  | 
| Defined in Data.Scientific | |
| NFData Scientific | |
| Defined in Data.Scientific Methods rnf :: Scientific -> () # | |
| FromField Scientific | int2, int4, int8, float4, float8, numeric | 
| Defined in Database.PostgreSQL.Simple.FromField Methods | |
| HasSqlEqualityCheck PgExpressionSyntax Scientific | |
| Defined in Database.Beam.Postgres.Syntax Methods sqlEqE :: Proxy Scientific -> PgExpressionSyntax -> PgExpressionSyntax -> PgExpressionSyntax # sqlNeqE :: Proxy Scientific -> PgExpressionSyntax -> PgExpressionSyntax -> PgExpressionSyntax # sqlEqTriE :: Proxy Scientific -> PgExpressionSyntax -> PgExpressionSyntax -> PgExpressionSyntax # sqlNeqTriE :: Proxy Scientific -> PgExpressionSyntax -> PgExpressionSyntax -> PgExpressionSyntax # | |
| HasSqlQuantifiedEqualityCheck PgExpressionSyntax Scientific | |
| Defined in Database.Beam.Postgres.Syntax Methods sqlQEqE :: Proxy Scientific -> Maybe (Sql92ExpressionQuantifierSyntax PgExpressionSyntax) -> PgExpressionSyntax -> PgExpressionSyntax -> PgExpressionSyntax # sqlQNeqE :: Proxy Scientific -> Maybe (Sql92ExpressionQuantifierSyntax PgExpressionSyntax) -> PgExpressionSyntax -> PgExpressionSyntax -> PgExpressionSyntax # | |
| HasSqlValueSyntax PgValueSyntax Scientific | |
| Defined in Database.Beam.Postgres.Syntax Methods | |
| FromBackendRow Postgres Scientific | |
| Defined in Database.Beam.Postgres.Types Methods fromBackendRow :: FromBackendRowM Postgres Scientific # valuesNeeded :: Proxy Postgres -> Proxy Scientific -> Int # | |
| ToField (PGRange Scientific) | |
| Defined in Database.PostgreSQL.Simple.Range Methods toField :: PGRange Scientific -> Action # | |
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
type LocalTimestamp = Unbounded LocalTime #
type UTCTimestamp = Unbounded UTCTime #
type ZonedTimestamp = Unbounded ZonedTime #
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
Time of day as represented in hour, minute and second (with picoseconds), typically used to express local time of day.
Instances
The Modified Julian Day is a standard count of days, with zero being the day 1858-11-17.
Instances
Re-exports for the deriveGeneric plus deriveVinyl combination
module Data.Coerce
data Proxy (t :: k) :: forall k. k -> * #
Proxy is a type that holds no data, but has a phantom parameter of
 arbitrary type (or even kind). Its use is to provide type information, even
 though there is no value available of that type (or it may be too costly to
 create one).
Historically, Proxy :: Proxy a'undefined :: a' idiom.
>>>Proxy :: Proxy (Void, Int -> Int)Proxy
Proxy can even hold types of higher kinds,
>>>Proxy :: Proxy EitherProxy
>>>Proxy :: Proxy FunctorProxy
>>>Proxy :: Proxy complicatedStructureProxy
Constructors
| Proxy | 
Instances
| Generic1 (Proxy :: k -> *) | |
| Monad (Proxy :: * -> *) | Since: base-4.7.0.0 | 
| Functor (Proxy :: * -> *) | Since: base-4.7.0.0 | 
| Applicative (Proxy :: * -> *) | Since: base-4.7.0.0 | 
| Foldable (Proxy :: * -> *) | Since: base-4.7.0.0 | 
| Defined in Data.Foldable Methods fold :: Monoid m => Proxy m -> m # foldMap :: Monoid m => (a -> m) -> Proxy a -> m # foldr :: (a -> b -> b) -> b -> Proxy a -> b # foldr' :: (a -> b -> b) -> b -> Proxy a -> b # foldl :: (b -> a -> b) -> b -> Proxy a -> b # foldl' :: (b -> a -> b) -> b -> Proxy a -> b # foldr1 :: (a -> a -> a) -> Proxy a -> a # foldl1 :: (a -> a -> a) -> Proxy a -> a # elem :: Eq a => a -> Proxy a -> Bool # maximum :: Ord a => Proxy a -> a # minimum :: Ord a => Proxy a -> a # | |
| Traversable (Proxy :: * -> *) | Since: base-4.7.0.0 | 
| Representable (Proxy :: * -> *) | |
| FromJSON1 (Proxy :: * -> *) | |
| Alternative (Proxy :: * -> *) | Since: base-4.9.0.0 | 
| MonadPlus (Proxy :: * -> *) | Since: base-4.9.0.0 | 
| Bounded (Proxy t) | |
| Enum (Proxy s) | Since: base-4.7.0.0 | 
| Eq (Proxy s) | Since: base-4.7.0.0 | 
| Ord (Proxy s) | Since: base-4.7.0.0 | 
| Read (Proxy t) | Since: base-4.7.0.0 | 
| Show (Proxy s) | Since: base-4.7.0.0 | 
| Ix (Proxy s) | Since: base-4.7.0.0 | 
| Defined in Data.Proxy | |
| Generic (Proxy t) | |
| Semigroup (Proxy s) | Since: base-4.9.0.0 | 
| Monoid (Proxy s) | Since: base-4.7.0.0 | 
| FromJSON (Proxy a) | |
| type Rep1 (Proxy :: k -> *) | |
| type Rep (Proxy :: * -> *) | |
| type Rep (Proxy t) | |
| type Code (Proxy t) | |
| Defined in Generics.SOP.Instances | |
| type DatatypeInfoOf (Proxy t) | |
| Defined in Generics.SOP.Instances type DatatypeInfoOf (Proxy t) = ADT "Data.Proxy" "Proxy" (Constructor "Proxy" ': ([] :: [ConstructorInfo])) | |
data Associativity #
Datatype to represent the associativity of a constructor
Constructors
| LeftAssociative | |
| RightAssociative | |
| NotAssociative | 
Instances
The code of a datatype.
This is a list of lists of its components. The outer list contains one element per constructor. The inner list contains one element per constructor argument (field).
Example: The datatype
data Tree = Leaf Int | Node Tree Tree
is supposed to have the following code:
type instance Code (Tree a) = '[ '[ Int ] , '[ Tree, Tree ] ]
Instances
| type Code Bool | |
| type Code Ordering | |
| type Code () | |
| Defined in Generics.SOP.Instances | |
| type Code DataRep | |
| type Code ConstrRep | |
| type Code Fixity | |
| type Code FormatAdjustment | |
| Defined in Generics.SOP.Instances | |
| type Code FormatSign | |
| Defined in Generics.SOP.Instances | |
| type Code FieldFormat | |
| Defined in Generics.SOP.Instances type Code FieldFormat = (Maybe Int ': (Maybe Int ': (Maybe FormatAdjustment ': (Maybe FormatSign ': (Bool ': (String ': (Char ': ([] :: [*])))))))) ': ([] :: [[*]]) | |
| type Code FormatParse | |
| Defined in Generics.SOP.Instances | |
| type Code Version | |
| type Code PatternMatchFail | |
| Defined in Generics.SOP.Instances | |
| type Code RecSelError | |
| Defined in Generics.SOP.Instances | |
| type Code RecConError | |
| Defined in Generics.SOP.Instances | |
| type Code RecUpdError | |
| Defined in Generics.SOP.Instances | |
| type Code NoMethodError | |
| Defined in Generics.SOP.Instances | |
| type Code NonTermination | |
| Defined in Generics.SOP.Instances | |
| type Code NestedAtomically | |
| Defined in Generics.SOP.Instances | |
| type Code Errno | |
| type Code BlockedIndefinitelyOnMVar | |
| Defined in Generics.SOP.Instances | |
| type Code BlockedIndefinitelyOnSTM | |
| Defined in Generics.SOP.Instances | |
| type Code Deadlock | |
| Defined in Generics.SOP.Instances | |
| type Code AssertionFailed | |
| Defined in Generics.SOP.Instances | |
| type Code AsyncException | |
| Defined in Generics.SOP.Instances | |
| type Code ArrayException | |
| Defined in Generics.SOP.Instances | |
| type Code ExitCode | |
| type Code BufferMode | |
| Defined in Generics.SOP.Instances | |
| type Code Newline | |
| type Code NewlineMode | |
| Defined in Generics.SOP.Instances | |
| type Code SeekMode | |
| type Code MaskingState | |
| Defined in Generics.SOP.Instances | |
| type Code IOException | |
| Defined in Generics.SOP.Instances | |
| type Code ErrorCall | |
| type Code ArithException | |
| Defined in Generics.SOP.Instances | |
| type Code All | |
| type Code Any | |
| type Code CChar | |
| type Code CSChar | |
| type Code CUChar | |
| type Code CShort | |
| type Code CUShort | |
| type Code CInt | |
| type Code CUInt | |
| type Code CLong | |
| type Code CULong | |
| type Code CLLong | |
| type Code CULLong | |
| type Code CFloat | |
| type Code CDouble | |
| type Code CPtrdiff | |
| type Code CSize | |
| type Code CWchar | |
| type Code CSigAtomic | |
| Defined in Generics.SOP.Instances | |
| type Code CClock | |
| type Code CTime | |
| type Code CUSeconds | |
| type Code CSUSeconds | |
| Defined in Generics.SOP.Instances | |
| type Code CIntPtr | |
| type Code CUIntPtr | |
| type Code CIntMax | |
| type Code CUIntMax | |
| type Code IOMode | |
| type Code Lexeme | |
| type Code Number | |
| type Code GeneralCategory | |
| Defined in Generics.SOP.Instances type Code GeneralCategory = ([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': ([] :: [[*]])))))))))))))))))))))))))))))) | |
| type Code [a] | |
| Defined in Generics.SOP.Instances | |
| type Code (Maybe a) | |
| type Code (Complex a) | |
| Defined in Generics.SOP.Instances | |
| type Code (Fixed a) | |
| type Code (ArgOrder a) | |
| type Code (OptDescr a) | |
| type Code (ArgDescr a) | |
| type Code (First a) | |
| type Code (Last a) | |
| type Code (Dual a) | |
| Defined in Generics.SOP.Instances | |
| type Code (Endo a) | |
| Defined in Generics.SOP.Instances | |
| type Code (Sum a) | |
| Defined in Generics.SOP.Instances | |
| type Code (Product a) | |
| Defined in Generics.SOP.Instances | |
| type Code (Down a) | |
| Defined in Generics.SOP.Instances | |
| type Code (I a) | |
| Defined in Generics.SOP.Instances | |
| type Code (Either a b) | |
| type Code (a, b) | |
| Defined in Generics.SOP.Instances | |
| type Code (Proxy t) | |
| Defined in Generics.SOP.Instances | |
| type Code (a, b, c) | |
| Defined in Generics.SOP.Instances | |
| type Code (K a b) | |
| Defined in Generics.SOP.Instances | |
| type Code (a, b, c, d) | |
| Defined in Generics.SOP.Instances | |
| type Code (a, b, c, d, e) | |
| Defined in Generics.SOP.Instances | |
| type Code ((f :.: g) p) | |
| Defined in Generics.SOP.Instances | |
| type Code (a, b, c, d, e, f) | |
| Defined in Generics.SOP.Instances | |
| type Code (a, b, c, d, e, f, g) | |
| Defined in Generics.SOP.Instances | |
| type Code (a, b, c, d, e, f, g, h) | |
| Defined in Generics.SOP.Instances | |
| type Code (a, b, c, d, e, f, g, h, i) | |
| Defined in Generics.SOP.Instances | |
| type Code (a, b, c, d, e, f, g, h, i, j) | |
| Defined in Generics.SOP.Instances | |
| type Code (a, b, c, d, e, f, g, h, i, j, k) | |
| Defined in Generics.SOP.Instances | |
| type Code (a, b, c, d, e, f, g, h, i, j, k, l) | |
| Defined in Generics.SOP.Instances | |
| type Code (a, b, c, d, e, f, g, h, i, j, k, l, m) | |
| Defined in Generics.SOP.Instances | |
| type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n) | |
| Defined in Generics.SOP.Instances | |
| type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) | |
| Defined in Generics.SOP.Instances | |
| type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) | |
| Defined in Generics.SOP.Instances | |
| type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) | |
| Defined in Generics.SOP.Instances | |
| type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) | |
| Defined in Generics.SOP.Instances | |
| type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) | |
| Defined in Generics.SOP.Instances | |
| type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) | |
| Defined in Generics.SOP.Instances | |
| type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) | |
| Defined in Generics.SOP.Instances | |
| type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) | |
| Defined in Generics.SOP.Instances | |
| type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w) | |
| Defined in Generics.SOP.Instances | |
| type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x) | |
| Defined in Generics.SOP.Instances | |
| type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y) | |
| Defined in Generics.SOP.Instances | |
| type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) | |
| Defined in Generics.SOP.Instances type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z) = (a ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': (i ': (j ': (k ': (l ': (m ': (n ': (o ': (p ': (q ': (r ': (s ': (t ': (u ': (v ': (w ': (x ': (y ': (z ': ([] :: [*]))))))))))))))))))))))))))) ': ([] :: [[*]]) | |
| type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26) | |
| Defined in Generics.SOP.Instances type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26) = (a ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': (i ': (j ': (k ': (l ': (m ': (n ': (o ': (p ': (q ': (r ': (s ': (t ': (u ': (v ': (w ': (x ': (y ': (z ': (t26 ': ([] :: [*])))))))))))))))))))))))))))) ': ([] :: [[*]]) | |
| type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27) | |
| Defined in Generics.SOP.Instances type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27) = (a ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': (i ': (j ': (k ': (l ': (m ': (n ': (o ': (p ': (q ': (r ': (s ': (t ': (u ': (v ': (w ': (x ': (y ': (z ': (t26 ': (t27 ': ([] :: [*]))))))))))))))))))))))))))))) ': ([] :: [[*]]) | |
| type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28) | |
| Defined in Generics.SOP.Instances type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28) = (a ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': (i ': (j ': (k ': (l ': (m ': (n ': (o ': (p ': (q ': (r ': (s ': (t ': (u ': (v ': (w ': (x ': (y ': (z ': (t26 ': (t27 ': (t28 ': ([] :: [*])))))))))))))))))))))))))))))) ': ([] :: [[*]]) | |
| type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28, t29) | |
| Defined in Generics.SOP.Instances type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v, w, x, y, z, t26, t27, t28, t29) = (a ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': (i ': (j ': (k ': (l ': (m ': (n ': (o ': (p ': (q ': (r ': (s ': (t ': (u ': (v ': (w ': (x ': (y ': (z ': (t26 ': (t27 ': (t28 ': (t29 ': ([] :: [*]))))))))))))))))))))))))))))))) ': ([] :: [[*]]) | |
to :: Generic a => Rep a -> a #
Converts from a structural representation back to the original value.
class HasDatatypeInfo a where #
A class of datatypes that have associated metadata.
It is possible to use the sum-of-products approach to generic programming without metadata. If you need metadata in a function, an additional constraint on this class is in order.
You typically don't define instances of this class by hand, but
 rather derive the class instance automatically. See the documentation
 of Generic for the options.
Methods
datatypeInfo :: proxy a -> DatatypeInfo (Code a) #
Term-level datatype info; by default, the term-level datatype info is produced from the type-level info.
type IsProductType a (xs :: [*]) = (Generic a, Code a ~ (xs ': ([] :: [[*]]))) #
Constraint that captures that a datatype is a product type, i.e., a type with a single constructor.
It also gives access to the code for the arguments of that constructor.
Since: generics-sop-0.3.1.0
type IsEnumType a = (Generic a, All ([*] ~ ([] :: [*])) (Code a)) #
Constraint that captures that a datatype is an enumeration type, i.e., none of the constructors have any arguments.
Since: generics-sop-0.3.1.0
type IsWrappedType a x = (Generic a, Code a ~ ((x ': ([] :: [*])) ': ([] :: [[*]]))) #
Constraint that captures that a datatype is a single-constructor, single-field datatype. This always holds for newtype-defined types, but it can also be true for data-defined types.
The constraint also gives access to the type that is wrapped.
Since: generics-sop-0.3.1.0
type IsNewtype a x = (IsWrappedType a x, Coercible a x) #
Constraint that captures that a datatype is a newtype. This makes use of the fact that newtypes are always coercible to the type they wrap, whereas datatypes are not.
Since: generics-sop-0.3.1.0
constructorName :: ConstructorInfo xs -> ConstructorName #
The name of a constructor.
Since: generics-sop-0.2.3.0
constructorInfo :: DatatypeInfo xss -> NP ConstructorInfo xss #
The constructor info for a datatype (or newtype).
Since: generics-sop-0.2.3.0
datatypeName :: DatatypeInfo xss -> DatatypeName #
The name of a datatype (or newtype).
Since: generics-sop-0.2.3.0
moduleName :: DatatypeInfo xss -> ModuleName #
The module name where a datatype is defined.
Since: generics-sop-0.2.3.0
data DatatypeInfo (a :: [[*]]) where #
Metadata for a datatype.
A value of type DatatypeInfo cCode c
The constructor indicates whether the datatype has been declared using newtype
 or not.
Constructors
| ADT :: DatatypeInfo a | |
| Newtype :: DatatypeInfo ((x ': ([] :: [*])) ': ([] :: [[*]])) | 
Instances
| All (Compose Eq ConstructorInfo) xs => Eq (DatatypeInfo xs) | |
| Defined in Generics.SOP.Metadata Methods (==) :: DatatypeInfo xs -> DatatypeInfo xs -> Bool # (/=) :: DatatypeInfo xs -> DatatypeInfo xs -> Bool # | |
| (All (Compose Eq ConstructorInfo) xs, All (Compose Ord ConstructorInfo) xs) => Ord (DatatypeInfo xs) | |
| Defined in Generics.SOP.Metadata Methods compare :: DatatypeInfo xs -> DatatypeInfo xs -> Ordering # (<) :: DatatypeInfo xs -> DatatypeInfo xs -> Bool # (<=) :: DatatypeInfo xs -> DatatypeInfo xs -> Bool # (>) :: DatatypeInfo xs -> DatatypeInfo xs -> Bool # (>=) :: DatatypeInfo xs -> DatatypeInfo xs -> Bool # max :: DatatypeInfo xs -> DatatypeInfo xs -> DatatypeInfo xs # min :: DatatypeInfo xs -> DatatypeInfo xs -> DatatypeInfo xs # | |
| All (Compose Show ConstructorInfo) xs => Show (DatatypeInfo xs) | |
| Defined in Generics.SOP.Metadata Methods showsPrec :: Int -> DatatypeInfo xs -> ShowS # show :: DatatypeInfo xs -> String # showList :: [DatatypeInfo xs] -> ShowS # | |
data ConstructorInfo (a :: [*]) where #
Metadata for a single constructors.
This is indexed by the product structure of the constructor components.
Constructors
| Constructor :: ConstructorInfo a | |
| Infix :: ConstructorInfo (x ': (y ': ([] :: [*]))) | |
| Record :: ConstructorInfo a | 
Instances
For records, this functor maps the component to its selector name.
Instances
| Functor FieldInfo | |
| Eq (FieldInfo a) | |
| Ord (FieldInfo a) | |
| Defined in Generics.SOP.Metadata | |
| Show (FieldInfo a) | |
type DatatypeName = String #
The name of a datatype.
type ModuleName = String #
The name of a module.
type ConstructorName = String #
The name of a data constructor.
Arguments
| :: All2 c xss | |
| => proxy c | |
| -> r | what to do if first is smaller | 
| -> (forall (xs :: [k]). All c xs => NP f xs -> NP g xs -> r) | what to do if both are equal | 
| -> r | what to do if first is larger | 
| -> SOP f xss | |
| -> SOP g xss | |
| -> r | 
Constrained version of compare_SOP.
Since: generics-sop-0.3.2.0
Arguments
| :: r | what to do if first is smaller | 
| -> (forall (xs :: [k]). NP f xs -> NP g xs -> r) | what to do if both are equal | 
| -> r | what to do if first is larger | 
| -> SOP f xss | |
| -> SOP g xss | |
| -> r | 
Compare two sums of products with respect to the choice in the sum they are making.
Only the sum structure is used for comparison.
 This is a small wrapper around ccompare_NS for
 a common special case.
Since: generics-sop-0.3.2.0
Arguments
| :: All c xs | |
| => proxy c | |
| -> r | what to do if first is smaller | 
| -> (forall (x :: k). c x => f x -> g x -> r) | what to do if both are equal | 
| -> r | what to do if first is larger | 
| -> NS f xs | |
| -> NS g xs | |
| -> r | 
Constrained version of compare_NS.
Since: generics-sop-0.3.2.0
Arguments
| :: r | what to do if first is smaller | 
| -> (forall (x :: k). f x -> g x -> r) | what to do if both are equal | 
| -> r | what to do if first is larger | 
| -> NS f xs | |
| -> NS g xs | |
| -> r | 
Compare two sums with respect to the choice they are making.
A value that chooses the first option is considered smaller than one that chooses the second option.
If the choices are different, then either the first (if the first is smaller than the second) or the third (if the first is larger than the second) argument are called. If both choices are equal, then the second argument is called, which has access to the elements contained in the sums.
Since: generics-sop-0.3.2.0
apInjs_POP :: SListI xss => POP f xss -> [SOP f xss] #
Apply injections to a product of product.
This operates on the outer product only. Given a product containing all possible choices (that are products), produce a list of sums (of products) by applying each injection to the appropriate element.
Example:
>>>apInjs_POP (POP ((I 'x' :* Nil) :* (I True :* I 2 :* Nil) :* Nil))[SOP (Z (I 'x' :* Nil)),SOP (S (Z (I True :* I 2 :* Nil)))]
apInjs_NP :: SListI xs => NP f xs -> [NS f xs] #
Apply injections to a product.
Given a product containing all possible choices, produce a list of sums by applying each injection to the appropriate element.
Example:
>>>apInjs_NP (I 'x' :* I True :* I 2 :* Nil)[Z (I 'x'),S (Z (I True)),S (S (Z (I 2)))]
shift :: Injection f xs a2 -> Injection f (x ': xs) a2 #
Shift an injection.
Given an injection, return an injection into a sum that is one component larger.
shiftInjection :: Injection f xs a2 -> Injection f (x ': xs) a2 #
Shift an injection.
Given an injection, return an injection into a sum that is one component larger.
injections :: SListI xs => NP (Injection f xs) xs #
Compute all injections into an n-ary sum.
Each element of the resulting product contains one of the injections.
unZ :: NS f (x ': ([] :: [k])) -> f x #
Extract the payload from a unary sum.
For larger sums, this function would be partial, so it is only provided with a rather restrictive type.
Example:
>>>unZ (Z (I 'x'))I 'x'
Since: generics-sop-0.2.2.0
data NS (a :: k -> *) (b :: [k]) :: forall k. (k -> *) -> [k] -> * where #
An n-ary sum.
The sum is parameterized by a type constructor f and
 indexed by a type-level list xs. The length of the list
 determines the number of choices in the sum and if the
 i-th element of the list is of type x, then the i-th
 choice of the sum is of type f x.
The constructor names are chosen to resemble Peano-style
 natural numbers, i.e., Z is for "zero", and S is for
 "successor". Chaining S and Z chooses the corresponding
 component of the sum.
Examples:
Z :: f x -> NS f (x ': xs) S . Z :: f y -> NS f (x ': y ': xs) S . S . Z :: f z -> NS f (x ': y ': z ': xs) ...
Note that empty sums (indexed by an empty list) have no non-bottom elements.
Two common instantiations of f are the identity functor I
 and the constant functor K. For I, the sum becomes a
 direct generalization of the Either type to arbitrarily many
 choices. For K a
In the context of the SOP approach to generic programming, an n-ary sum describes the top-level structure of a datatype, which is a choice between all of its constructors.
Examples:
Z (I 'x') :: NS I '[ Char, Bool ] S (Z (I True)) :: NS I '[ Char, Bool ] S (Z (K 1)) :: NS (K Int) '[ Char, Bool ]
Instances
| HTrans (NS :: (k1 -> *) -> [k1] -> *) (NS :: (k2 -> *) -> [k2] -> *) | |
| HAp (NS :: (k -> *) -> [k] -> *) | |
| HCollapse (NS :: (k -> *) -> [k] -> *) | |
| Defined in Generics.SOP.NS | |
| HTraverse_ (NS :: (k -> *) -> [k] -> *) | |
| Defined in Generics.SOP.NS Methods hctraverse_ :: (AllN NS c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> NS f xs -> g () # htraverse_ :: (SListIN NS xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> NS f xs -> g () # | |
| HSequence (NS :: (k -> *) -> [k] -> *) | |
| Defined in Generics.SOP.NS Methods hsequence' :: (SListIN NS xs, Applicative f) => NS (f :.: g) xs -> f (NS g xs) # hctraverse' :: (AllN NS c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> NS f xs -> g (NS f' xs) # htraverse' :: (SListIN NS xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> NS f xs -> g (NS f' xs) # | |
| HIndex (NS :: (k -> *) -> [k] -> *) | |
| Defined in Generics.SOP.NS | |
| HApInjs (NS :: (k -> *) -> [k] -> *) | |
| HExpand (NS :: (k -> *) -> [k] -> *) | |
| All (Compose Eq f) xs => Eq (NS f xs) | |
| (All (Compose Eq f) xs, All (Compose Ord f) xs) => Ord (NS f xs) | |
| All (Compose Show f) xs => Show (NS f xs) | |
| All (Compose NFData f) xs => NFData (NS f xs) | Since: generics-sop-0.2.5.0 | 
| Defined in Generics.SOP.NS | |
| type Same (NS :: (k1 -> *) -> [k1] -> *) | |
| type Prod (NS :: (k -> *) -> [k] -> *) | |
| type SListIN (NS :: (k -> *) -> [k] -> *) | |
| Defined in Generics.SOP.NS | |
| type CollapseTo (NS :: (k -> *) -> [k] -> *) a | |
| Defined in Generics.SOP.NS | |
| type AllN (NS :: (k -> *) -> [k] -> *) (c :: k -> Constraint) | |
| Defined in Generics.SOP.NS | |
newtype SOP (f :: k -> *) (xss :: [[k]]) :: forall k. (k -> *) -> [[k]] -> * #
A sum of products.
This is a 'newtype' for an NS of an NP. The elements of the
 (inner) products are applications of the parameter f. The type
 SOP is indexed by the list of lists that determines the sizes
 of both the (outer) sum and all the (inner) products, as well as
 the types of all the elements of the inner products.
An SOP I
Instances
| HTrans (SOP :: (k1 -> *) -> [[k1]] -> *) (SOP :: (k2 -> *) -> [[k2]] -> *) | |
| HAp (SOP :: (k -> *) -> [[k]] -> *) | |
| HCollapse (SOP :: (k -> *) -> [[k]] -> *) | |
| Defined in Generics.SOP.NS | |
| HTraverse_ (SOP :: (k -> *) -> [[k]] -> *) | |
| Defined in Generics.SOP.NS Methods hctraverse_ :: (AllN SOP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> SOP f xs -> g () # htraverse_ :: (SListIN SOP xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> SOP f xs -> g () # | |
| HSequence (SOP :: (k -> *) -> [[k]] -> *) | |
| Defined in Generics.SOP.NS Methods hsequence' :: (SListIN SOP xs, Applicative f) => SOP (f :.: g) xs -> f (SOP g xs) # hctraverse' :: (AllN SOP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> SOP f xs -> g (SOP f' xs) # htraverse' :: (SListIN SOP xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> SOP f xs -> g (SOP f' xs) # | |
| HIndex (SOP :: (k -> *) -> [[k]] -> *) | |
| Defined in Generics.SOP.NS | |
| HApInjs (SOP :: (k -> *) -> [[k]] -> *) | |
| HExpand (SOP :: (k -> *) -> [[k]] -> *) | |
| Eq (NS (NP f) xss) => Eq (SOP f xss) | |
| Ord (NS (NP f) xss) => Ord (SOP f xss) | |
| Show (NS (NP f) xss) => Show (SOP f xss) | |
| NFData (NS (NP f) xss) => NFData (SOP f xss) | Since: generics-sop-0.2.5.0 | 
| Defined in Generics.SOP.NS | |
| type Same (SOP :: (k1 -> *) -> [[k1]] -> *) | |
| type Prod (SOP :: (k -> *) -> [[k]] -> *) | |
| type SListIN (SOP :: (k -> *) -> [[k]] -> *) | |
| Defined in Generics.SOP.NS | |
| type CollapseTo (SOP :: (k -> *) -> [[k]] -> *) a | |
| Defined in Generics.SOP.NS | |
| type AllN (SOP :: (k -> *) -> [[k]] -> *) (c :: k -> Constraint) | |
| Defined in Generics.SOP.NS | |
type Injection (f :: k -> *) (xs :: [k]) = f -.-> (K (NS f xs) :: k -> *) #
The type of injections into an n-ary sum.
If you expand the type synonyms and newtypes involved, you get
Injection f xs a = (f -.-> K (NS f xs)) a ~= f a -> K (NS f xs) a ~= f a -> NS f xs
If we pick a to be an element of xs, this indeed corresponds to an
 injection into the sum.
hcliftA3' :: (All2 c xss, Prod h ~ (NP :: ([k] -> *) -> [[k]] -> *), HAp h) => proxy c -> (forall (xs :: [k]). All c xs => f xs -> f' xs -> f'' xs -> f''' xs) -> Prod h f xss -> Prod h f' xss -> h f'' xss -> h f''' xss #
Like hcliftA', but for ternay functions.
hcliftA2' :: (All2 c xss, Prod h ~ (NP :: ([k] -> *) -> [[k]] -> *), HAp h) => proxy c -> (forall (xs :: [k]). All c xs => f xs -> f' xs -> f'' xs) -> Prod h f xss -> h f' xss -> h f'' xss #
Like hcliftA', but for binary functions.
hcliftA' :: (All2 c xss, Prod h ~ (NP :: ([k] -> *) -> [[k]] -> *), HAp h) => proxy c -> (forall (xs :: [k]). All c xs => f xs -> f' xs) -> h f xss -> h f' xss #
Lift a constrained function operating on a list-indexed structure to a function on a list-of-list-indexed structure.
This is a variant of hcliftA.
Specification:
hcliftA'p f xs =hpure(fn_2$ \AllDictC-> f) `hap`allDict_NPp `hap` xs
Instances:
hcliftA'::All2c xss => proxy c -> (forall xs.Allc xs => f xs -> f' xs) ->NPf xss ->NPf' xsshcliftA'::All2c xss => proxy c -> (forall xs.Allc xs => f xs -> f' xs) ->NSf xss ->NSf' xss
shiftProjection :: Projection f xs a2 -> Projection f (x ': xs) a2 #
projections :: SListI xs => NP (Projection f xs) xs #
Compute all projections from an n-ary product.
Each element of the resulting product contains one of the projections.
fromList :: SListI xs => [a] -> Maybe (NP (K a :: k -> *) xs) #
Construct a homogeneous n-ary product from a normal Haskell list.
Returns Nothing if the length of the list does not exactly match the
 expected size of the product.
data NP (a :: k -> *) (b :: [k]) :: forall k. (k -> *) -> [k] -> * where #
An n-ary product.
The product is parameterized by a type constructor f and
 indexed by a type-level list xs. The length of the list
 determines the number of elements in the product, and if the
 i-th element of the list is of type x, then the i-th
 element of the product is of type f x.
The constructor names are chosen to resemble the names of the list constructors.
Two common instantiations of f are the identity functor I
 and the constant functor K. For I, the product becomes a
 heterogeneous list, where the type-level list describes the
 types of its components. For K a
In the context of the SOP approach to generic programming, an n-ary product describes the structure of the arguments of a single data constructor.
Examples:
I 'x' :* I True :* Nil :: NP I '[ Char, Bool ] K 0 :* K 1 :* Nil :: NP (K Int) '[ Char, Bool ] Just 'x' :* Nothing :* Nil :: NP Maybe '[ Char, Bool ]
Instances
| HTrans (NP :: (k1 -> *) -> [k1] -> *) (NP :: (k2 -> *) -> [k2] -> *) | |
| HPure (NP :: (k -> *) -> [k] -> *) | |
| HAp (NP :: (k -> *) -> [k] -> *) | |
| HCollapse (NP :: (k -> *) -> [k] -> *) | |
| Defined in Generics.SOP.NP | |
| HTraverse_ (NP :: (k -> *) -> [k] -> *) | |
| Defined in Generics.SOP.NP Methods hctraverse_ :: (AllN NP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> NP f xs -> g () # htraverse_ :: (SListIN NP xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> NP f xs -> g () # | |
| HSequence (NP :: (k -> *) -> [k] -> *) | |
| Defined in Generics.SOP.NP Methods hsequence' :: (SListIN NP xs, Applicative f) => NP (f :.: g) xs -> f (NP g xs) # hctraverse' :: (AllN NP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> NP f xs -> g (NP f' xs) # htraverse' :: (SListIN NP xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> NP f xs -> g (NP f' xs) # | |
| All (Compose Eq f) xs => Eq (NP f xs) | |
| (All (Compose Eq f) xs, All (Compose Ord f) xs) => Ord (NP f xs) | |
| All (Compose Show f) xs => Show (NP f xs) | |
| All (Compose NFData f) xs => NFData (NP f xs) | Since: generics-sop-0.2.5.0 | 
| Defined in Generics.SOP.NP | |
| type AllZipN (NP :: (k -> *) -> [k] -> *) (c :: a -> b -> Constraint) | |
| Defined in Generics.SOP.NP | |
| type Same (NP :: (k1 -> *) -> [k1] -> *) | |
| type Prod (NP :: (k -> *) -> [k] -> *) | |
| type UnProd (NP :: (k -> *) -> [k] -> *) | |
| type SListIN (NP :: (k -> *) -> [k] -> *) | |
| Defined in Generics.SOP.NP | |
| type CollapseTo (NP :: (k -> *) -> [k] -> *) a | |
| Defined in Generics.SOP.NP | |
| type AllN (NP :: (k -> *) -> [k] -> *) (c :: k -> Constraint) | |
| Defined in Generics.SOP.NP | |
newtype POP (f :: k -> *) (xss :: [[k]]) :: forall k. (k -> *) -> [[k]] -> * #
A product of products.
This is a 'newtype' for an NP of an NP. The elements of the
 inner products are applications of the parameter f. The type
 POP is indexed by the list of lists that determines the lengths
 of both the outer and all the inner products, as well as the types
 of all the elements of the inner products.
A POP is reminiscent of a two-dimensional table (but the inner
 lists can all be of different length). In the context of the SOP
 approach to generic programming, a POP is useful to represent
 information that is available for all arguments of all constructors
 of a datatype.
Instances
| HTrans (POP :: (k1 -> *) -> [[k1]] -> *) (POP :: (k2 -> *) -> [[k2]] -> *) | |
| HPure (POP :: (k -> *) -> [[k]] -> *) | |
| HAp (POP :: (k -> *) -> [[k]] -> *) | |
| HCollapse (POP :: (k -> *) -> [[k]] -> *) | |
| Defined in Generics.SOP.NP | |
| HTraverse_ (POP :: (k -> *) -> [[k]] -> *) | |
| Defined in Generics.SOP.NP Methods hctraverse_ :: (AllN POP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> POP f xs -> g () # htraverse_ :: (SListIN POP xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> POP f xs -> g () # | |
| HSequence (POP :: (k -> *) -> [[k]] -> *) | |
| Defined in Generics.SOP.NP Methods hsequence' :: (SListIN POP xs, Applicative f) => POP (f :.: g) xs -> f (POP g xs) # hctraverse' :: (AllN POP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> POP f xs -> g (POP f' xs) # htraverse' :: (SListIN POP xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> POP f xs -> g (POP f' xs) # | |
| Eq (NP (NP f) xss) => Eq (POP f xss) | |
| Ord (NP (NP f) xss) => Ord (POP f xss) | |
| Show (NP (NP f) xss) => Show (POP f xss) | |
| NFData (NP (NP f) xss) => NFData (POP f xss) | Since: generics-sop-0.2.5.0 | 
| Defined in Generics.SOP.NP | |
| type AllZipN (POP :: (k -> *) -> [[k]] -> *) (c :: a -> b -> Constraint) | |
| Defined in Generics.SOP.NP | |
| type Same (POP :: (k1 -> *) -> [[k1]] -> *) | |
| type Prod (POP :: (k -> *) -> [[k]] -> *) | |
| type UnProd (POP :: (k -> *) -> [[k]] -> *) | |
| type SListIN (POP :: (k -> *) -> [[k]] -> *) | |
| Defined in Generics.SOP.NP | |
| type CollapseTo (POP :: (k -> *) -> [[k]] -> *) a | |
| Defined in Generics.SOP.NP | |
| type AllN (POP :: (k -> *) -> [[k]] -> *) (c :: k -> Constraint) | |
| Defined in Generics.SOP.NP | |
type Projection (f :: k -> *) (xs :: [k]) = (K (NP f xs) :: k -> *) -.-> f #
The type of projections from an n-ary product.
htoI :: (AllZipN (Prod h1) (LiftedCoercible f I) xs ys, HTrans h1 h2) => h1 f xs -> h2 I ys #
Specialization of hcoerce.
Since: generics-sop-0.3.1.0
hfromI :: (AllZipN (Prod h1) (LiftedCoercible I f) xs ys, HTrans h1 h2) => h1 I xs -> h2 f ys #
Specialization of hcoerce.
Since: generics-sop-0.3.1.0
hsequenceK :: (SListIN h xs, SListIN (Prod h) xs, Applicative f, HSequence h) => h (K (f a) :: k -> *) xs -> f (h (K a :: k -> *) xs) #
Special case of hsequence' where g = .K a
hsequence :: (SListIN h xs, SListIN (Prod h) xs, HSequence h, Applicative f) => h f xs -> f (h I xs) #
Special case of hsequence' where g = .I
hcfor :: (HSequence h, AllN h c xs, Applicative g) => proxy c -> h f xs -> (forall a. c a => f a -> g a) -> g (h I xs) #
Flipped version of hctraverse.
Since: generics-sop-0.3.2.0
hctraverse :: (HSequence h, AllN h c xs, Applicative g) => proxy c -> (forall a. c a => f a -> g a) -> h f xs -> g (h I xs) #
Special case of hctraverse' where f' = .I
Since: generics-sop-0.3.2.0
hcfoldMap :: (HTraverse_ h, AllN h c xs, Monoid m) => proxy c -> (forall (a :: k). c a => f a -> m) -> h f xs -> m #
Special case of hctraverse_.
Since: generics-sop-0.3.2.0
hcfor_ :: (HTraverse_ h, AllN h c xs, Applicative g) => proxy c -> h f xs -> (forall (a :: k). c a => f a -> g ()) -> g () #
Flipped version of hctraverse_.
Since: generics-sop-0.3.2.0
hczipWith3 :: (AllN (Prod h) c xs, HAp h, HAp (Prod h)) => proxy c -> (forall (a :: k). c a => f a -> f' a -> f'' a -> f''' a) -> Prod h f xs -> Prod h f' xs -> h f'' xs -> h f''' xs #
Another name for hcliftA3.
Since: generics-sop-0.2
hczipWith :: (AllN (Prod h) c xs, HAp h, HAp (Prod h)) => proxy c -> (forall (a :: k). c a => f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs #
Another name for hcliftA2.
Since: generics-sop-0.2
hcmap :: (AllN (Prod h) c xs, HAp h) => proxy c -> (forall (a :: k). c a => f a -> f' a) -> h f xs -> h f' xs #
Another name for hcliftA.
Since: generics-sop-0.2
hcliftA3 :: (AllN (Prod h) c xs, HAp h, HAp (Prod h)) => proxy c -> (forall (a :: k). c a => f a -> f' a -> f'' a -> f''' a) -> Prod h f xs -> Prod h f' xs -> h f'' xs -> h f''' xs #
hcliftA2 :: (AllN (Prod h) c xs, HAp h, HAp (Prod h)) => proxy c -> (forall (a :: k). c a => f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs #
hcliftA :: (AllN (Prod h) c xs, HAp h) => proxy c -> (forall (a :: k). c a => f a -> f' a) -> h f xs -> h f' xs #
hzipWith3 :: (SListIN (Prod h) xs, HAp h, HAp (Prod h)) => (forall (a :: k). f a -> f' a -> f'' a -> f''' a) -> Prod h f xs -> Prod h f' xs -> h f'' xs -> h f''' xs #
Another name for hliftA3.
Since: generics-sop-0.2
hzipWith :: (SListIN (Prod h) xs, HAp h, HAp (Prod h)) => (forall (a :: k). f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs #
Another name for hliftA2.
Since: generics-sop-0.2
hmap :: (SListIN (Prod h) xs, HAp h) => (forall (a :: k). f a -> f' a) -> h f xs -> h f' xs #
Another name for hliftA.
Since: generics-sop-0.2
hliftA3 :: (SListIN (Prod h) xs, HAp h, HAp (Prod h)) => (forall (a :: k). f a -> f' a -> f'' a -> f''' a) -> Prod h f xs -> Prod h f' xs -> h f'' xs -> h f''' xs #
A generalized form of liftA3,
 which in turn is a generalized zipWith3.
Takes a lifted ternary function and uses it to combine three structures of equal shape into a single structure.
It either takes three product structures to a product structure, or two product structures and one sum structure to a sum structure.
Specification:
hliftA3f xs ys zs =hpure(fn_3f) `hap` xs `hap` ys `hap` zs
Instances:
hliftA3,liftA3_NP::SListIxs => (forall a. f a -> f' a -> f'' a -> f''' a) ->NPf xs ->NPf' xs ->NPf'' xs ->NPf''' xshliftA3,liftA3_NS::SListIxs => (forall a. f a -> f' a -> f'' a -> f''' a) ->NPf xs ->NPf' xs ->NSf'' xs ->NSf''' xshliftA3,liftA3_POP::SListI2xss => (forall a. f a -> f' a -> f'' a -> f''' a) ->POPf xss ->POPf' xss ->POPf'' xss ->POPf''' xshliftA3,liftA3_SOP::SListI2xss => (forall a. f a -> f' a -> f'' a -> f''' a) ->POPf xss ->POPf' xss ->SOPf'' xss ->SOPf''' xs
hliftA2 :: (SListIN (Prod h) xs, HAp h, HAp (Prod h)) => (forall (a :: k). f a -> f' a -> f'' a) -> Prod h f xs -> h f' xs -> h f'' xs #
A generalized form of liftA2,
 which in turn is a generalized zipWith.
Takes a lifted binary function and uses it to combine two structures of equal shape into a single structure.
It either takes two product structures to a product structure, or one product and one sum structure to a sum structure.
Specification:
hliftA2f xs ys =hpure(fn_2f) `hap` xs `hap` ys
Instances:
hliftA2,liftA2_NP::SListIxs => (forall a. f a -> f' a -> f'' a) ->NPf xs ->NPf' xs ->NPf'' xshliftA2,liftA2_NS::SListIxs => (forall a. f a -> f' a -> f'' a) ->NPf xs ->NSf' xs ->NSf'' xshliftA2,liftA2_POP::SListI2xss => (forall a. f a -> f' a -> f'' a) ->POPf xss ->POPf' xss ->POPf'' xsshliftA2,liftA2_SOP::SListI2xss => (forall a. f a -> f' a -> f'' a) ->POPf xss ->SOPf' xss ->SOPf'' xss
hliftA :: (SListIN (Prod h) xs, HAp h) => (forall (a :: k). f a -> f' a) -> h f xs -> h f' xs #
A generalized form of liftA,
 which in turn is a generalized map.
Takes a lifted function and applies it to every element of a structure while preserving its shape.
Specification:
hliftAf xs =hpure(fnf) `hap` xs
Instances:
hliftA,liftA_NP::SListIxs => (forall a. f a -> f' a) ->NPf xs ->NPf' xshliftA,liftA_NS::SListIxs => (forall a. f a -> f' a) ->NSf xs ->NSf' xshliftA,liftA_POP::SListI2xss => (forall a. f a -> f' a) ->POPf xss ->POPf' xsshliftA,liftA_SOP::SListI2xss => (forall a. f a -> f' a) ->SOPf xss ->SOPf' xss
fn_4 :: (f a -> f' a -> f'' a -> f''' a -> f'''' a) -> (f -.-> (f' -.-> (f'' -.-> (f''' -.-> f'''')))) a #
Construct a quarternary lifted function.
fn_3 :: (f a -> f' a -> f'' a -> f''' a) -> (f -.-> (f' -.-> (f'' -.-> f'''))) a #
Construct a ternary lifted function.
fn :: (f a -> f' a) -> (f -.-> f') a #
Construct a lifted function.
Same as Fn. Only available for uniformity with the
 higher-arity versions.
class HPure (h :: (k -> *) -> l -> *) where #
Methods
hpure :: SListIN h xs => (forall (a :: k). f a) -> h f xs #
Corresponds to pure directly.
Instances:
hpure,pure_NP::SListIxs => (forall a. f a) ->NPf xshpure,pure_POP::SListI2xss => (forall a. f a) ->POPf xss
hcpure :: AllN h c xs => proxy c -> (forall (a :: k). c a => f a) -> h f xs #
A variant of hpure that allows passing in a constrained
 argument.
Calling hcpure f ss :: h f xs causes f to be
 applied at all the types that are contained in xs. Therefore,
 the constraint c has to be satisfied for all elements of xs,
 which is what AllMap h c xs
Morally, hpure is a special case of hcpure where the
 constraint is empty. However, it is in the nature of how AllMap
 is defined as well as current GHC limitations that it is tricky
 to prove to GHC in general that AllMap h c NoConstraint xshpure
 separately and directly, and make it a member of the class.
Instances:
hcpure,cpure_NP:: (Allc xs ) => proxy c -> (forall a. c a => f a) ->NPf xshcpure,cpure_POP:: (All2c xss) => proxy c -> (forall a. c a => f a) ->POPf xss
newtype ((f :: k -> *) -.-> (g :: k -> *)) (a :: k) :: forall k. (k -> *) -> (k -> *) -> k -> * infixr 1 #
Lifted functions.
type family Prod (h :: (k -> *) -> l -> *) :: (k -> *) -> l -> * #
Maps a structure containing sums to the corresponding product structure.
class (Prod (Prod h) ~ Prod h, HPure (Prod h)) => HAp (h :: (k -> *) -> l -> *) where #
A generalization of <*>.
Minimal complete definition
Methods
hap :: Prod h (f -.-> g) xs -> h f xs -> h g xs #
Corresponds to <*>.
For products (NP) as well as products of products
 (POP), the correspondence is rather direct. We combine
 a structure containing (lifted) functions and a compatible structure
 containing corresponding arguments into a compatible structure
 containing results.
The same combinator can also be used to combine a product structure of functions with a sum structure of arguments, which then results in another sum structure of results. The sum structure determines which part of the product structure will be used.
Instances:
hap,ap_NP::NP(f -.-> g) xs ->NPf xs ->NPg xshap,ap_NS::NP(f -.-> g) xs ->NSf xs ->NSg xshap,ap_POP::POP(f -.-> g) xss ->POPf xss ->POPg xsshap,ap_SOP::POP(f -.-> g) xss ->SOPf xss ->SOPg xss
type family CollapseTo (h :: (k -> *) -> l -> *) x :: * #
Maps products to lists, and sums to identities.
Instances
| type CollapseTo (NS :: (k -> *) -> [k] -> *) a | |
| Defined in Generics.SOP.NS | |
| type CollapseTo (SOP :: (k -> *) -> [[k]] -> *) a | |
| Defined in Generics.SOP.NS | |
| type CollapseTo (NP :: (k -> *) -> [k] -> *) a | |
| Defined in Generics.SOP.NP | |
| type CollapseTo (POP :: (k -> *) -> [[k]] -> *) a | |
| Defined in Generics.SOP.NP | |
class HCollapse (h :: (k -> *) -> l -> *) where #
A class for collapsing a heterogeneous structure into a homogeneous one.
Minimal complete definition
Methods
hcollapse :: SListIN h xs => h (K a :: k -> *) xs -> CollapseTo h a #
Collapse a heterogeneous structure with homogeneous elements into a homogeneous structure.
If a heterogeneous structure is instantiated to the constant
 functor K, then it is in fact homogeneous. This function
 maps such a value to a simpler Haskell datatype reflecting that.
 An NS (K a)a, and an NP (K a)as.
Instances:
hcollapse,collapse_NP::NP(Ka) xs -> [a]hcollapse,collapse_NS::NS(Ka) xs -> ahcollapse,collapse_POP::POP(Ka) xss -> [[a]]hcollapse,collapse_SOP::SOP(Ka) xss -> [a]
Instances
| HCollapse (SOP :: (k -> *) -> [[k]] -> *) | |
| Defined in Generics.SOP.NS | |
| HCollapse (NS :: (k -> *) -> [k] -> *) | |
| Defined in Generics.SOP.NS | |
| HCollapse (POP :: (k -> *) -> [[k]] -> *) | |
| Defined in Generics.SOP.NP | |
| HCollapse (NP :: (k -> *) -> [k] -> *) | |
| Defined in Generics.SOP.NP | |
class HTraverse_ (h :: (k -> *) -> l -> *) where #
Minimal complete definition
Methods
hctraverse_ :: (AllN h c xs, Applicative g) => proxy c -> (forall (a :: k). c a => f a -> g ()) -> h f xs -> g () #
Corresponds to traverse_.
Instances:
hctraverse_,ctraverse__NP:: (Allc xs ,Applicativeg) => proxy c -> (forall a. c a => f a -> g ()) ->NPf xs -> g ()hctraverse_,ctraverse__NS:: (All2c xs ,Applicativeg) => proxy c -> (forall a. c a => f a -> g ()) ->NSf xs -> g ()hctraverse_,ctraverse__POP:: (Allc xss,Applicativeg) => proxy c -> (forall a. c a => f a -> g ()) ->POPf xss -> g ()hctraverse_,ctraverse__SOP:: (All2c xss,Applicativeg) => proxy c -> (forall a. c a => f a -> g ()) ->SOPf xss -> g ()
Since: generics-sop-0.3.2.0
htraverse_ :: (SListIN h xs, Applicative g) => (forall (a :: k). f a -> g ()) -> h f xs -> g () #
Unconstrained version of hctraverse_.
Instances:
traverse_,traverse__NP:: (SListIxs , 'Applicative g') => (forall a. f a -> g ()) ->NPf xs -> g ()traverse_,traverse__NS:: (SListIxs , 'Applicative g') => (forall a. f a -> g ()) ->NSf xs -> g ()traverse_,traverse__POP:: (SListI2xss, 'Applicative g') => (forall a. f a -> g ()) ->POPf xss -> g ()traverse_,traverse__SOP:: (SListI2xss, 'Applicative g') => (forall a. f a -> g ()) ->SOPf xss -> g ()
Since: generics-sop-0.3.2.0
Instances
| HTraverse_ (SOP :: (k -> *) -> [[k]] -> *) | |
| Defined in Generics.SOP.NS Methods hctraverse_ :: (AllN SOP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> SOP f xs -> g () # htraverse_ :: (SListIN SOP xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> SOP f xs -> g () # | |
| HTraverse_ (NS :: (k -> *) -> [k] -> *) | |
| Defined in Generics.SOP.NS Methods hctraverse_ :: (AllN NS c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> NS f xs -> g () # htraverse_ :: (SListIN NS xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> NS f xs -> g () # | |
| HTraverse_ (POP :: (k -> *) -> [[k]] -> *) | |
| Defined in Generics.SOP.NP Methods hctraverse_ :: (AllN POP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> POP f xs -> g () # htraverse_ :: (SListIN POP xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> POP f xs -> g () # | |
| HTraverse_ (NP :: (k -> *) -> [k] -> *) | |
| Defined in Generics.SOP.NP Methods hctraverse_ :: (AllN NP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g ()) -> NP f xs -> g () # htraverse_ :: (SListIN NP xs, Applicative g) => (forall (a :: k0). f a -> g ()) -> NP f xs -> g () # | |
class HAp h => HSequence (h :: (k -> *) -> l -> *) where #
A generalization of sequenceA.
Minimal complete definition
Methods
hsequence' :: (SListIN h xs, Applicative f) => h (f :.: g) xs -> f (h g xs) #
Corresponds to sequenceA.
Lifts an applicative functor out of a structure.
Instances:
hsequence',sequence'_NP:: (SListIxs ,Applicativef) =>NP(f:.:g) xs -> f (NPg xs )hsequence',sequence'_NS:: (SListIxs ,Applicativef) =>NS(f:.:g) xs -> f (NSg xs )hsequence',sequence'_POP:: (SListI2xss,Applicativef) =>POP(f:.:g) xss -> f (POPg xss)hsequence',sequence'_SOP:: (SListI2xss,Applicativef) =>SOP(f:.:g) xss -> f (SOPg xss)
hctraverse' :: (AllN h c xs, Applicative g) => proxy c -> (forall (a :: k). c a => f a -> g (f' a)) -> h f xs -> g (h f' xs) #
Corresponds to traverse.
Instances:
hctraverse',ctraverse'_NP:: (Allc xs ,Applicativeg) => proxy c -> (forall a. c a => f a -> g (f' a)) ->NPf xs -> g (NPf' xs )hctraverse',ctraverse'_NS:: (All2c xs ,Applicativeg) => proxy c -> (forall a. c a => f a -> g (f' a)) ->NSf xs -> g (NSf' xs )hctraverse',ctraverse'_POP:: (Allc xss,Applicativeg) => proxy c -> (forall a. c a => f a -> g (f' a)) ->POPf xss -> g (POPf' xss)hctraverse',ctraverse'_SOP:: (All2c xss,Applicativeg) => proxy c -> (forall a. c a => f a -> g (f' a)) ->SOPf xss -> g (SOPf' xss)
Since: generics-sop-0.3.2.0
htraverse' :: (SListIN h xs, Applicative g) => (forall (a :: k). f a -> g (f' a)) -> h f xs -> g (h f' xs) #
Unconstrained variant of htraverse'.
Instances:
htraverse',traverse'_NP:: (SListIxs ,Applicativeg) => (forall a. c a => f a -> g (f' a)) ->NPf xs -> g (NPf' xs )htraverse',traverse'_NS:: (SListI2xs ,Applicativeg) => (forall a. c a => f a -> g (f' a)) ->NSf xs -> g (NSf' xs )htraverse',traverse'_POP:: (SListIxss,Applicativeg) => (forall a. c a => f a -> g (f' a)) ->POPf xss -> g (POPf' xss)htraverse',traverse'_SOP:: (SListI2xss,Applicativeg) => (forall a. c a => f a -> g (f' a)) ->SOPf xss -> g (SOPf' xss)
Since: generics-sop-0.3.2.0
Instances
| HSequence (SOP :: (k -> *) -> [[k]] -> *) | |
| Defined in Generics.SOP.NS Methods hsequence' :: (SListIN SOP xs, Applicative f) => SOP (f :.: g) xs -> f (SOP g xs) # hctraverse' :: (AllN SOP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> SOP f xs -> g (SOP f' xs) # htraverse' :: (SListIN SOP xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> SOP f xs -> g (SOP f' xs) # | |
| HSequence (NS :: (k -> *) -> [k] -> *) | |
| Defined in Generics.SOP.NS Methods hsequence' :: (SListIN NS xs, Applicative f) => NS (f :.: g) xs -> f (NS g xs) # hctraverse' :: (AllN NS c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> NS f xs -> g (NS f' xs) # htraverse' :: (SListIN NS xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> NS f xs -> g (NS f' xs) # | |
| HSequence (POP :: (k -> *) -> [[k]] -> *) | |
| Defined in Generics.SOP.NP Methods hsequence' :: (SListIN POP xs, Applicative f) => POP (f :.: g) xs -> f (POP g xs) # hctraverse' :: (AllN POP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> POP f xs -> g (POP f' xs) # htraverse' :: (SListIN POP xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> POP f xs -> g (POP f' xs) # | |
| HSequence (NP :: (k -> *) -> [k] -> *) | |
| Defined in Generics.SOP.NP Methods hsequence' :: (SListIN NP xs, Applicative f) => NP (f :.: g) xs -> f (NP g xs) # hctraverse' :: (AllN NP c xs, Applicative g) => proxy c -> (forall (a :: k0). c a => f a -> g (f' a)) -> NP f xs -> g (NP f' xs) # htraverse' :: (SListIN NP xs, Applicative g) => (forall (a :: k0). f a -> g (f' a)) -> NP f xs -> g (NP f' xs) # | |
class HIndex (h :: (k -> *) -> l -> *) where #
A class for determining which choice in a sum-like structure a value represents.
Minimal complete definition
Methods
If h is a sum-like structure representing a choice
 between n different options, and x is a value of
 type h f xs, then hindex x0 and n - 1 representing the index of the choice
 made by x.
Instances:
hindex,index_NS::NSf xs -> Inthindex,index_SOP::SOPf xs -> Int
Examples:
>>>hindex (S (S (Z (I False))))2>>>hindex (Z (K ()))0>>>hindex (SOP (S (Z (I True :* I 'x' :* Nil))))1
Since: generics-sop-0.2.4.0
type family UnProd (h :: (k -> *) -> l -> *) :: (k -> *) -> l -> * #
Maps a structure containing products to the corresponding sum structure.
Since: generics-sop-0.2.4.0
class UnProd (Prod h) ~ h => HApInjs (h :: (k -> *) -> l -> *) where #
A class for applying all injections corresponding to a sum-like structure to a table containing suitable arguments.
Minimal complete definition
Methods
hapInjs :: SListIN h xs => Prod h f xs -> [h f xs] #
For a given table (product-like structure), produce a list where each element corresponds to the application of an injection function into the corresponding sum-like structure.
Instances:
hapInjs,apInjs_NP::SListIxs =>NPf xs -> [NSf xs ]hapInjs,apInjs_SOP::SListI2xss =>POPf xs -> [SOPf xss]
Examples:
>>>hapInjs (I 'x' :* I True :* I 2 :* Nil) :: [NS I '[Char, Bool, Int]][Z (I 'x'),S (Z (I True)),S (S (Z (I 2)))]
>>>hapInjs (POP ((I 'x' :* Nil) :* (I True :* I 2 :* Nil) :* Nil)) :: [SOP I '[ '[Char], '[Bool, Int]]][SOP (Z (I 'x' :* Nil)),SOP (S (Z (I True :* I 2 :* Nil)))]
Unfortunately the type-signatures are required in GHC-7.10 and older.
Since: generics-sop-0.2.4.0
class HExpand (h :: (k -> *) -> l -> *) where #
A class for expanding sum structures into corresponding product structures, filling in the slots not targeted by the sum with default values.
Since: generics-sop-0.2.5.0
Methods
hexpand :: SListIN (Prod h) xs => (forall (x :: k). f x) -> h f xs -> Prod h f xs #
Expand a given sum structure into a corresponding product structure by placing the value contained in the sum into the corresponding position in the product, and using the given default value for all other positions.
Instances:
hexpand,expand_NS::SListIxs => (forall x . f x) ->NSf xs ->NPf xshexpand,expand_SOP::SListI2xss => (forall x . f x) ->SOPf xss ->POPf xss
Examples:
>>>hexpand Nothing (S (Z (Just 3))) :: NP Maybe '[Char, Int, Bool]Nothing :* Just 3 :* Nothing :* Nil>>>hexpand [] (SOP (S (Z ([1,2] :* "xyz" :* Nil)))) :: POP [] '[ '[Bool], '[Int, Char] ]POP (([] :* Nil) :* ([1,2] :* "xyz" :* Nil) :* Nil)
Since: generics-sop-0.2.5.0
hcexpand :: AllN (Prod h) c xs => proxy c -> (forall (x :: k). c x => f x) -> h f xs -> Prod h f xs #
Variant of hexpand that allows passing a constrained default.
Instances:
hcexpand,cexpand_NS::Allc xs => proxy c -> (forall x . c x => f x) ->NSf xs ->NPf xshcexpand,cexpand_SOP::All2c xss => proxy c -> (forall x . c x => f x) ->SOPf xss ->POPf xss
Examples:
>>>hcexpand (Proxy :: Proxy Bounded) (I minBound) (S (Z (I 20))) :: NP I '[Bool, Int, Ordering]I False :* I 20 :* I LT :* Nil>>>hcexpand (Proxy :: Proxy Num) (I 0) (SOP (S (Z (I 1 :* I 2 :* Nil)))) :: POP I '[ '[Double], '[Int, Int] ]POP ((I 0.0 :* Nil) :* (I 1 :* I 2 :* Nil) :* Nil)
Since: generics-sop-0.2.5.0
class ((Same h1 :: (k2 -> *) -> l2 -> *) ~ h2, (Same h2 :: (k1 -> *) -> l1 -> *) ~ h1) => HTrans (h1 :: (k1 -> *) -> l1 -> *) (h2 :: (k2 -> *) -> l2 -> *) where #
A class for transforming structures into related structures with a different index list, as long as the index lists have the same shape and the elements and interpretation functions are suitably related.
Since: generics-sop-0.3.1.0
Methods
htrans :: AllZipN (Prod h1) c xs ys => proxy c -> (forall (x :: k1) (y :: k2). c x y => f x -> g y) -> h1 f xs -> h2 g ys #
Transform a structure into a related structure given a conversion function for the elements.
Since: generics-sop-0.3.1.0
hcoerce :: (AllZipN (Prod h1) (LiftedCoercible f g) xs ys, HTrans h1 h2) => h1 f xs -> h2 g ys #
Coerce a structure into a representationally equal structure.
Examples:
>>>hcoerce (I (Just LT) :* I (Just 'x') :* I (Just True) :* Nil) :: NP Maybe '[Ordering, Char, Bool]Just LT :* Just 'x' :* Just True :* Nil>>>hcoerce (SOP (Z (K True :* K False :* Nil))) :: SOP I '[ '[Bool, Bool], '[Bool] ]SOP (Z (I True :* I False :* Nil))
Since: generics-sop-0.3.1.0
class (AllF f xs, SListI xs) => All (f :: k -> Constraint) (xs :: [k]) #
Require a constraint for every element of a list.
If you have a datatype that is indexed over a type-level
 list, then you can use All to indicate that all elements
 of that type-level list must satisfy a given constraint.
Example: The constraint
All Eq '[ Int, Bool, Char ]
is equivalent to the constraint
(Eq Int, Eq Bool, Eq Char)
Example: A type signature such as
f :: All Eq xs => NP I xs -> ...
means that f can assume that all elements of the n-ary
 product satisfy Eq.
Instances
| (AllF f xs, SListI xs) => All (f :: k -> Constraint) (xs :: [k]) | |
| Defined in Generics.SOP.Constraint | |
type SListI2 = All (SListI :: [k] -> Constraint) #
Require a singleton for every inner list in a list of lists.
class (AllF (All f) xss, SListI xss) => All2 (f :: k -> Constraint) (xss :: [[k]]) #
Require a constraint for every element of a list of lists.
If you have a datatype that is indexed over a type-level
 list of lists, then you can use All2 to indicate that all
 elements of the innert lists must satisfy a given constraint.
Example: The constraint
All2 Eq '[ '[ Int ], '[ Bool, Char ] ]
is equivalent to the constraint
(Eq Int, Eq Bool, Eq Char)
Example: A type signature such as
f :: All2 Eq xss => SOP I xs -> ...
means that f can assume that all elements of the sum
 of product satisfy Eq.
Instances
| (AllF (All f) xss, SListI xss) => All2 (f :: k -> Constraint) (xss :: [[k]]) | |
| Defined in Generics.SOP.Constraint | |
class (SListI xs, SListI ys, SameShapeAs xs ys, SameShapeAs ys xs, AllZipF c xs ys) => AllZip (c :: a -> b -> Constraint) (xs :: [a]) (ys :: [b]) #
Require a constraint for pointwise for every pair of elements from two lists.
Example: The constraint
All (~) '[ Int, Bool, Char ] '[ a, b, c ]
is equivalent to the constraint
(Int ~ a, Bool ~ b, Char ~ c)
Since: generics-sop-0.3.1.0
Instances
| (SListI xs, SListI ys, SameShapeAs xs ys, SameShapeAs ys xs, AllZipF c xs ys) => AllZip (c :: a -> b -> Constraint) (xs :: [a]) (ys :: [b]) | |
| Defined in Generics.SOP.Constraint | |
type family SameShapeAs (xs :: [a]) (ys :: [b]) :: Constraint where ... #
Type family that forces a type-level list to be of the same shape as the given type-level list.
The main use of this constraint is to help type inference to learn something about otherwise unknown type-level lists.
Since: generics-sop-0.3.1.0
Equations
| SameShapeAs ([] :: [a]) (ys :: [b]) = ys ~ ([] :: [b]) | |
| SameShapeAs (x ': xs :: [a]) (ys :: [b]) = (ys ~ (Head ys ': Tail ys), SameShapeAs xs (Tail ys)) | 
class Coercible (f x) (g y) => LiftedCoercible (f :: k -> k0) (g :: k1 -> k0) (x :: k) (y :: k1) #
The constraint LiftedCoercible f g x y is equivalent
 to Coercible (f x) (g y).
Since: generics-sop-0.3.1.0
Instances
| Coercible (f x) (g y) => LiftedCoercible (f :: k2 -> k0) (g :: k1 -> k0) (x :: k2) (y :: k1) | |
| Defined in Generics.SOP.Constraint | |
class (AllZipF (AllZip f) xss yss, SListI xss, SListI yss, SameShapeAs xss yss, SameShapeAs yss xss) => AllZip2 (f :: a -> b -> Constraint) (xss :: [[a]]) (yss :: [[b]]) #
Require a constraint for pointwise for every pair of elements from two lists of lists.
Instances
| (AllZipF (AllZip f) xss yss, SListI xss, SListI yss, SameShapeAs xss yss, SameShapeAs yss xss) => AllZip2 (f :: a -> b -> Constraint) (xss :: [[a]]) (yss :: [[b]]) | |
| Defined in Generics.SOP.Constraint | |
class f (g x) => Compose (f :: k -> Constraint) (g :: k1 -> k) (x :: k1) infixr 9 #
Composition of constraints.
Note that the result of the composition must be a constraint,
 and therefore, in f , the kind of :. gf is k -> .
 The kind of Constraintg, however, is l -> k and can thus be an normal
 type constructor.
A typical use case is in connection with All on an NP or an
 NS. For example, in order to denote that all elements on an
 NP f xsShow, we can say All (Show :. f) xs
Since: generics-sop-0.2
Instances
| f (g x) => Compose (f :: k2 -> Constraint) (g :: k1 -> k2) (x :: k1) | |
| Defined in Generics.SOP.Constraint | |
class (f x, g x) => And (f :: k -> Constraint) (g :: k -> Constraint) (x :: k) infixl 7 #
Pairing of constraints.
Since: generics-sop-0.2
Instances
| (f x, g x) => And (f :: k -> Constraint) (g :: k -> Constraint) (x :: k) | |
| Defined in Generics.SOP.Constraint | |
A constraint that can always be satisfied.
Since: generics-sop-0.2
Instances
| Top (x :: k) | |
| Defined in Generics.SOP.Constraint | |
type family AllN (h :: (k -> *) -> l -> *) (c :: k -> Constraint) :: l -> Constraint #
A generalization of All and All2.
The family AllN expands to All or All2 depending on whether
 the argument is indexed by a list or a list of lists.
Instances
| type AllN (NS :: (k -> *) -> [k] -> *) (c :: k -> Constraint) | |
| Defined in Generics.SOP.NS | |
| type AllN (SOP :: (k -> *) -> [[k]] -> *) (c :: k -> Constraint) | |
| Defined in Generics.SOP.NS | |
| type AllN (NP :: (k -> *) -> [k] -> *) (c :: k -> Constraint) | |
| Defined in Generics.SOP.NP | |
| type AllN (POP :: (k -> *) -> [[k]] -> *) (c :: k -> Constraint) | |
| Defined in Generics.SOP.NP | |
type family AllZipN (h :: (k -> *) -> l -> *) (c :: k1 -> k2 -> Constraint) :: l1 -> l2 -> Constraint #
A generalization of AllZip and AllZip2.
The family AllZipN expands to AllZip or AllZip2 depending on
 whther the argument is indexed by a list or a list of lists.
Instances
| type AllZipN (NP :: (k -> *) -> [k] -> *) (c :: a -> b -> Constraint) | |
| Defined in Generics.SOP.NP | |
| type AllZipN (POP :: (k -> *) -> [[k]] -> *) (c :: a -> b -> Constraint) | |
| Defined in Generics.SOP.NP | |
lengthSing :: SListI xs => proxy xs -> Int #
Old name for lengthSList.
lengthSList :: SListI xs => proxy xs -> Int #
The length of a type-level list.
Since: generics-sop-0.2
data SList (a :: [k]) :: forall k. [k] -> * where #
Explicit singleton list.
A singleton list can be used to reveal the structure of
 a type-level list argument that the function is quantified
 over. For every type-level list xs, there is one non-bottom
 value of type SList xs
Note that these singleton lists are polymorphic in the list elements; we do not require a singleton representation for them.
Since: generics-sop-0.2
class SListI (xs :: [k]) where #
Implicit singleton list.
A singleton list can be used to reveal the structure of a type-level list argument that the function is quantified over.
The class SListI should have instances that match the
 constructors of SList.
Since: generics-sop-0.2
Minimal complete definition
class SListI xs => SingI (xs :: [k]) where #
General class for implicit singletons.
Just provided for limited backward compatibility.
Minimal complete definition
type Sing = (SList :: [k] -> *) #
Explicit singleton type.
Just provided for limited backward compatibility.
data Shape (a :: [k]) :: forall k. [k] -> * where #
Occassionally it is useful to have an explicit, term-level, representation of type-level lists (esp because of https://ghc.haskell.org/trac/ghc/ticket/9108)
mapKKK :: (a -> b -> c) -> K a d -> K b e -> K c f #
Lift the given function.
Since: generics-sop-0.2.5.0
mapKKI :: (a -> b -> c) -> K a d -> K b e -> I c #
Lift the given function.
Since: generics-sop-0.2.5.0
mapKIK :: (a -> b -> c) -> K a d -> I b -> K c e #
Lift the given function.
Since: generics-sop-0.2.5.0
mapIKK :: (a -> b -> c) -> I a -> K b d -> K c e #
Lift the given function.
Since: generics-sop-0.2.5.0
newtype K a (b :: k) :: forall k. * -> k -> * #
The constant type functor.
Like Constant, but kind-polymorphic
 in its second argument and with a shorter name.
Constructors
| K a | 
Instances
| Eq2 (K :: * -> * -> *) | Since: generics-sop-0.2.4.0 | 
| Ord2 (K :: * -> * -> *) | Since: generics-sop-0.2.4.0 | 
| Defined in Generics.SOP.BasicFunctors | |
| Read2 (K :: * -> * -> *) | Since: generics-sop-0.2.4.0 | 
| Defined in Generics.SOP.BasicFunctors Methods liftReadsPrec2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> Int -> ReadS (K a b) # liftReadList2 :: (Int -> ReadS a) -> ReadS [a] -> (Int -> ReadS b) -> ReadS [b] -> ReadS [K a b] # liftReadPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec (K a b) # liftReadListPrec2 :: ReadPrec a -> ReadPrec [a] -> ReadPrec b -> ReadPrec [b] -> ReadPrec [K a b] # | |
| Show2 (K :: * -> * -> *) | Since: generics-sop-0.2.4.0 | 
| NFData2 (K :: * -> * -> *) | Since: generics-sop-0.2.5.0 | 
| Defined in Generics.SOP.BasicFunctors | |
| Functor (K a :: * -> *) | |
| Monoid a => Applicative (K a :: * -> *) | |
| Foldable (K a :: * -> *) | |
| Defined in Generics.SOP.BasicFunctors Methods fold :: Monoid m => K a m -> m # foldMap :: Monoid m => (a0 -> m) -> K a a0 -> m # foldr :: (a0 -> b -> b) -> b -> K a a0 -> b # foldr' :: (a0 -> b -> b) -> b -> K a a0 -> b # foldl :: (b -> a0 -> b) -> b -> K a a0 -> b # foldl' :: (b -> a0 -> b) -> b -> K a a0 -> b # foldr1 :: (a0 -> a0 -> a0) -> K a a0 -> a0 # foldl1 :: (a0 -> a0 -> a0) -> K a a0 -> a0 # elem :: Eq a0 => a0 -> K a a0 -> Bool # maximum :: Ord a0 => K a a0 -> a0 # minimum :: Ord a0 => K a a0 -> a0 # | |
| Traversable (K a :: * -> *) | |
| Eq a => Eq1 (K a :: * -> *) | Since: generics-sop-0.2.4.0 | 
| Ord a => Ord1 (K a :: * -> *) | Since: generics-sop-0.2.4.0 | 
| Defined in Generics.SOP.BasicFunctors | |
| Read a => Read1 (K a :: * -> *) | Since: generics-sop-0.2.4.0 | 
| Defined in Generics.SOP.BasicFunctors | |
| Show a => Show1 (K a :: * -> *) | Since: generics-sop-0.2.4.0 | 
| NFData a => NFData1 (K a :: * -> *) | Since: generics-sop-0.2.5.0 | 
| Defined in Generics.SOP.BasicFunctors | |
| Eq a => Eq (K a b) | |
| Ord a => Ord (K a b) | |
| Read a => Read (K a b) | |
| Show a => Show (K a b) | |
| Generic (K a b) | |
| NFData a => NFData (K a b) | Since: generics-sop-0.2.5.0 | 
| Defined in Generics.SOP.BasicFunctors | |
| type Rep (K a b) | |
| Defined in Generics.SOP.BasicFunctors | |
| type Code (K a b) | |
| Defined in Generics.SOP.Instances | |
| type DatatypeInfoOf (K a b) | |
| Defined in Generics.SOP.Instances | |
The identity type functor.
Like Identity, but with a shorter name.
Constructors
| I a | 
Instances
| Monad I | |
| Functor I | |
| Applicative I | |
| Foldable I | |
| Defined in Generics.SOP.BasicFunctors Methods fold :: Monoid m => I m -> m # foldMap :: Monoid m => (a -> m) -> I a -> m # foldr :: (a -> b -> b) -> b -> I a -> b # foldr' :: (a -> b -> b) -> b -> I a -> b # foldl :: (b -> a -> b) -> b -> I a -> b # foldl' :: (b -> a -> b) -> b -> I a -> b # foldr1 :: (a -> a -> a) -> I a -> a # foldl1 :: (a -> a -> a) -> I a -> a # elem :: Eq a => a -> I a -> Bool # maximum :: Ord a => I a -> a # | |
| Traversable I | |
| Eq1 I | Since: generics-sop-0.2.4.0 | 
| Ord1 I | Since: generics-sop-0.2.4.0 | 
| Defined in Generics.SOP.BasicFunctors | |
| Read1 I | Since: generics-sop-0.2.4.0 | 
| Defined in Generics.SOP.BasicFunctors | |
| Show1 I | Since: generics-sop-0.2.4.0 | 
| NFData1 I | Since: generics-sop-0.2.5.0 | 
| Defined in Generics.SOP.BasicFunctors | |
| Eq a => Eq (I a) | |
| Ord a => Ord (I a) | |
| Read a => Read (I a) | |
| Show a => Show (I a) | |
| Generic (I a) | |
| NFData a => NFData (I a) | Since: generics-sop-0.2.5.0 | 
| Defined in Generics.SOP.BasicFunctors | |
| type Rep (I a) | |
| Defined in Generics.SOP.BasicFunctors | |
| type Code (I a) | |
| Defined in Generics.SOP.Instances | |
| type DatatypeInfoOf (I a) | |
| Defined in Generics.SOP.Instances | |
newtype ((f :: l -> *) :.: (g :: k -> l)) (p :: k) :: forall l k. (l -> *) -> (k -> l) -> k -> * infixr 7 #
Composition of functors.
Like Compose, but kind-polymorphic
 and with a shorter name.
Constructors
| Comp (f (g p)) | 
Instances
| (Functor f, Functor g) => Functor (f :.: g) | |
| (Applicative f, Applicative g) => Applicative (f :.: g) | Since: generics-sop-0.2.5.0 | 
| Defined in Generics.SOP.BasicFunctors | |
| (Foldable f, Foldable g) => Foldable (f :.: g) | Since: generics-sop-0.2.5.0 | 
| Defined in Generics.SOP.BasicFunctors Methods fold :: Monoid m => (f :.: g) m -> m # foldMap :: Monoid m => (a -> m) -> (f :.: g) a -> m # foldr :: (a -> b -> b) -> b -> (f :.: g) a -> b # foldr' :: (a -> b -> b) -> b -> (f :.: g) a -> b # foldl :: (b -> a -> b) -> b -> (f :.: g) a -> b # foldl' :: (b -> a -> b) -> b -> (f :.: g) a -> b # foldr1 :: (a -> a -> a) -> (f :.: g) a -> a # foldl1 :: (a -> a -> a) -> (f :.: g) a -> a # toList :: (f :.: g) a -> [a] # length :: (f :.: g) a -> Int # elem :: Eq a => a -> (f :.: g) a -> Bool # maximum :: Ord a => (f :.: g) a -> a # minimum :: Ord a => (f :.: g) a -> a # | |
| (Traversable f, Traversable g) => Traversable (f :.: g) | Since: generics-sop-0.2.5.0 | 
| Defined in Generics.SOP.BasicFunctors | |
| (Eq1 f, Eq1 g) => Eq1 (f :.: g) | Since: generics-sop-0.2.4.0 | 
| (Ord1 f, Ord1 g) => Ord1 (f :.: g) | Since: generics-sop-0.2.4.0 | 
| Defined in Generics.SOP.BasicFunctors | |
| (Read1 f, Read1 g) => Read1 (f :.: g) | Since: generics-sop-0.2.4.0 | 
| Defined in Generics.SOP.BasicFunctors | |
| (Show1 f, Show1 g) => Show1 (f :.: g) | Since: generics-sop-0.2.4.0 | 
| (NFData1 f, NFData1 g) => NFData1 (f :.: g) | Since: generics-sop-0.2.5.0 | 
| Defined in Generics.SOP.BasicFunctors | |
| (Eq1 f, Eq1 g, Eq a) => Eq ((f :.: g) a) | |
| (Ord1 f, Ord1 g, Ord a) => Ord ((f :.: g) a) | |
| Defined in Generics.SOP.BasicFunctors | |
| (Read1 f, Read1 g, Read a) => Read ((f :.: g) a) | |
| (Show1 f, Show1 g, Show a) => Show ((f :.: g) a) | |
| Generic ((f :.: g) p) | |
| NFData (f (g a)) => NFData ((f :.: g) a) | Since: generics-sop-0.2.5.0 | 
| Defined in Generics.SOP.BasicFunctors | |
| type Rep ((f :.: g) p) | |
| Defined in Generics.SOP.BasicFunctors | |
| type Code ((f :.: g) p) | |
| Defined in Generics.SOP.Instances | |
| type DatatypeInfoOf ((f :.: g) p) | |
| Defined in Generics.SOP.Instances | |
deriveGeneric :: Name -> Q [Dec] #
Generate generics-sop boilerplate for the given datatype.
This function takes the name of a datatype and generates:
- a Codeinstance
- a Genericinstance
- a HasDatatypeInfoinstance
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.