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

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

Frames.SQL.Beam.Postgres

Contents

Description

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

Synopsis

Usage Example

A. Interactive Workflow Steps

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

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

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

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

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

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

Import this module into Example:

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

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

   import NewBeamSchema


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

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

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

   import NewBeamSchema


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

   deriveGeneric ''Cart_usersT
   deriveVinyl ''Cart_usersT
   

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

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

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

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

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

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

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

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

B. Streaming Workflow Steps

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

1 - 4: Same as 'Interactive Workflow Steps'

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

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

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

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

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

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

A Note on 'Filter Lambdas'

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

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

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

or

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

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

Re-exports of the underlying modules

Re-exports of beam-core and beam-postgres

Postgres Column Types

data ByteString #

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

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

Instances
Eq ByteString 
Instance details

Defined in Data.ByteString.Internal

Data ByteString 
Instance details

Defined in Data.ByteString.Internal

Methods

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

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

toConstr :: ByteString -> Constr #

dataTypeOf :: ByteString -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord ByteString 
Instance details

Defined in Data.ByteString.Internal

Read ByteString 
Instance details

Defined in Data.ByteString.Internal

Show ByteString 
Instance details

Defined in Data.ByteString.Internal

IsString ByteString 
Instance details

Defined in Data.ByteString.Internal

Semigroup ByteString 
Instance details

Defined in Data.ByteString.Internal

Monoid ByteString 
Instance details

Defined in Data.ByteString.Internal

Chunk ByteString 
Instance details

Defined in Data.Attoparsec.Internal.Types

Associated Types

type ChunkElem ByteString :: * #

FoldCase ByteString

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

Instance details

Defined in Data.CaseInsensitive.Internal

NFData ByteString 
Instance details

Defined in Data.ByteString.Internal

Methods

rnf :: ByteString -> () #

ToHStoreText ByteString

Assumed to be UTF-8 encoded

Instance details

Defined in Database.PostgreSQL.Simple.HStore.Implementation

FromField ByteString

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

Instance details

Defined in Database.PostgreSQL.Simple.FromField

HasSqlEqualityCheck PgExpressionSyntax ByteString 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasSqlQuantifiedEqualityCheck PgExpressionSyntax ByteString 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasSqlValueSyntax Value ByteString 
Instance details

Defined in Database.Beam.Backend.SQL.AST

HasSqlValueSyntax PgValueSyntax ByteString 
Instance details

Defined in Database.Beam.Postgres.Syntax

FromBackendRow Postgres ByteString 
Instance details

Defined in Database.Beam.Postgres.Types

HasDefaultSqlDataTypeConstraints PgColumnSchemaSyntax ByteString 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasDefaultSqlDataType PgDataTypeSyntax ByteString 
Instance details

Defined in Database.Beam.Postgres.Syntax

FromBackendRow Postgres (Binary ByteString) 
Instance details

Defined in Database.Beam.Postgres.Types

FromField (Binary ByteString)

bytea

Instance details

Defined in Database.PostgreSQL.Simple.FromField

type State ByteString 
Instance details

Defined in Data.Attoparsec.Internal.Types

type State ByteString = Buffer
type ChunkElem ByteString 
Instance details

Defined in Data.Attoparsec.Internal.Types

data Text #

A space efficient, packed, unboxed Unicode text type.

Instances
FromJSON Text 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Text 
Instance details

Defined in Data.Aeson.Types.FromJSON

Chunk Text 
Instance details

Defined in Data.Attoparsec.Internal.Types

Associated Types

type ChunkElem Text :: * #

FoldCase Text 
Instance details

Defined in Data.CaseInsensitive.Internal

Methods

foldCase :: Text -> Text #

foldCaseList :: [Text] -> [Text]

ToHStoreText Text 
Instance details

Defined in Database.PostgreSQL.Simple.HStore.Implementation

FromField Text

name, text, "char", bpchar, varchar

Instance details

Defined in Database.PostgreSQL.Simple.FromField

HasSqlEqualityCheck SqlSyntaxBuilder Text 
Instance details

Defined in Database.Beam.Query.Ord

HasSqlEqualityCheck Expression Text 
Instance details

Defined in Database.Beam.Query.Ord

HasSqlEqualityCheck PgExpressionSyntax Text 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasSqlQuantifiedEqualityCheck SqlSyntaxBuilder Text 
Instance details

Defined in Database.Beam.Query.Ord

HasSqlQuantifiedEqualityCheck Expression Text 
Instance details

Defined in Database.Beam.Query.Ord

HasSqlQuantifiedEqualityCheck PgExpressionSyntax Text 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasSqlValueSyntax SqlSyntaxBuilder Text 
Instance details

Defined in Database.Beam.Backend.SQL.Builder

HasSqlValueSyntax Value Text 
Instance details

Defined in Database.Beam.Backend.SQL.AST

Methods

sqlValueSyntax :: Text -> Value #

HasSqlValueSyntax PgValueSyntax Text 
Instance details

Defined in Database.Beam.Postgres.Syntax

FromBackendRow Postgres Text 
Instance details

Defined in Database.Beam.Postgres.Types

Beamable t => ProjectibleWithPredicate AnyType Text (t (QField s)) 
Instance details

Defined in Database.Beam.Query.Internal

Methods

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

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

Defined in Database.Beam.Query.Internal

Methods

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

ProjectibleWithPredicate AnyType Text (QField s a) 
Instance details

Defined in Database.Beam.Query.Internal

Methods

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

HasSqlEqualityCheck PgExpressionSyntax (CI Text) 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasSqlQuantifiedEqualityCheck PgExpressionSyntax (CI Text) 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasSqlValueSyntax PgValueSyntax (CI Text) 
Instance details

Defined in Database.Beam.Postgres.Syntax

FromBackendRow Postgres (CI Text) 
Instance details

Defined in Database.Beam.Postgres.Types

FromField (CI Text)

citext

Instance details

Defined in Database.PostgreSQL.Simple.FromField

IsSqlExpressionSyntaxStringType SqlSyntaxBuilder Text 
Instance details

Defined in Database.Beam.Backend.SQL.Builder

IsSqlExpressionSyntaxStringType Expression Text 
Instance details

Defined in Database.Beam.Backend.SQL.AST

IsSqlExpressionSyntaxStringType PgExpressionSyntax Text 
Instance details

Defined in Database.Beam.Postgres.Syntax

(IsSql92ExpressionSyntax syntax, HasSqlValueSyntax (Sql92ExpressionValueSyntax syntax) [Char]) => IsString (QGenExpr context syntax s Text) 
Instance details

Defined in Database.Beam.Query.Internal

Methods

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

type VectorFor Text 
Instance details

Defined in Frames.InCore

type State Text 
Instance details

Defined in Data.Attoparsec.Internal.Types

type State Text = Buffer
type ChunkElem Text 
Instance details

Defined in Data.Attoparsec.Internal.Types

type Item Text 
Instance details

Defined in Data.Text

type Item Text = Char

data UUID #

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

Instances
Eq UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

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

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

Data UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

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

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

toConstr :: UUID -> Constr #

dataTypeOf :: UUID -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

compare :: UUID -> UUID -> Ordering #

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

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

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

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

max :: UUID -> UUID -> UUID #

min :: UUID -> UUID -> UUID #

Read UUID 
Instance details

Defined in Data.UUID.Types.Internal

Show UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

showsPrec :: Int -> UUID -> ShowS #

show :: UUID -> String #

showList :: [UUID] -> ShowS #

Hashable UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

hashWithSalt :: Int -> UUID -> Int #

hash :: UUID -> Int #

FromJSON UUID 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey UUID 
Instance details

Defined in Data.Aeson.Types.FromJSON

Storable UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

sizeOf :: UUID -> Int #

alignment :: UUID -> Int #

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

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

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

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

peek :: Ptr UUID -> IO UUID #

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

Binary UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

put :: UUID -> Put #

get :: Get UUID #

putList :: [UUID] -> Put #

NFData UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

rnf :: UUID -> () #

FromField UUID

uuid

Instance details

Defined in Database.PostgreSQL.Simple.FromField

Random UUID 
Instance details

Defined in Data.UUID.Types.Internal

Methods

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

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

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

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

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

randomIO :: IO UUID #

HasSqlEqualityCheck PgExpressionSyntax UUID 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasSqlQuantifiedEqualityCheck PgExpressionSyntax UUID 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasSqlValueSyntax PgValueSyntax UUID 
Instance details

Defined in Database.Beam.Postgres.Syntax

FromBackendRow Postgres UUID 
Instance details

Defined in Database.Beam.Postgres.Types

HasDefaultSqlDataTypeConstraints PgColumnSchemaSyntax UUID 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasDefaultSqlDataType PgDataTypeSyntax UUID 
Instance details

Defined in Database.Beam.Postgres.Syntax

data Scientific #

An arbitrary-precision number represented using scientific notation.

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

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

Instances
Eq Scientific

Scientific numbers can be safely compared for equality. No magnitude 10^e is calculated so there's no risk of a blowup in space or time when comparing scientific numbers coming from untrusted sources.

Instance details

Defined in Data.Scientific

Fractional Scientific

WARNING: recip and / will throw an error when their outputs are repeating decimals.

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

Instance details

Defined in Data.Scientific

Data Scientific 
Instance details

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: + and - compute the Integer magnitude: 10^e where e is the difference between the base10Exponents of the arguments. If these methods are applied to arguments which have huge exponents this could fill up all space and crash your program! So don't apply these methods to scientific numbers coming from untrusted sources. The other methods can be used safely.

Instance details

Defined in Data.Scientific

Ord Scientific

Scientific numbers can be safely compared for ordering. No magnitude 10^e is calculated so there's no risk of a blowup in space or time when comparing scientific numbers coming from untrusted sources.

Instance details

Defined in Data.Scientific

Read Scientific

Supports the skipping of parentheses and whitespaces. Example:

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

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

Instance details

Defined in Data.Scientific

Real Scientific

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

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

Instance details

Defined in Data.Scientific

RealFrac Scientific

WARNING: the methods of the RealFrac instance need to compute the magnitude 10^e. If applied to a huge exponent this could take a long time. Even worse, when the destination type is unbounded (i.e. Integer) it could fill up all space and crash your program!

Instance details

Defined in Data.Scientific

Show Scientific

See formatScientific if you need more control over the rendering.

Instance details

Defined in Data.Scientific

Hashable Scientific

A hash can be safely calculated from a Scientific. No magnitude 10^e is calculated so there's no risk of a blowup in space or time when hashing scientific numbers coming from untrusted sources.

Instance details

Defined in Data.Scientific

FromJSON Scientific 
Instance details

Defined in Data.Aeson.Types.FromJSON

Binary Scientific

Note that in the future I intend to change the type of the base10Exponent from Int to Integer. To be forward compatible the Binary instance already encodes the exponent as Integer.

Instance details

Defined in Data.Scientific

NFData Scientific 
Instance details

Defined in Data.Scientific

Methods

rnf :: Scientific -> () #

FromField Scientific

int2, int4, int8, float4, float8, numeric

Instance details

Defined in Database.PostgreSQL.Simple.FromField

HasSqlEqualityCheck PgExpressionSyntax Scientific 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasSqlQuantifiedEqualityCheck PgExpressionSyntax Scientific 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasSqlValueSyntax PgValueSyntax Scientific 
Instance details

Defined in Database.Beam.Postgres.Syntax

FromBackendRow Postgres Scientific 
Instance details

Defined in Database.Beam.Postgres.Types

ToField (PGRange Scientific) 
Instance details

Defined in Database.PostgreSQL.Simple.Range

data UTCTime #

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

Instances
Eq UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

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

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

Data UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

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

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

toConstr :: UTCTime -> Constr #

dataTypeOf :: UTCTime -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

FromJSON UTCTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey UTCTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

NFData UTCTime 
Instance details

Defined in Data.Time.Clock.Internal.UTCTime

Methods

rnf :: UTCTime -> () #

FromField UTCTime

timestamptz

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField UTCTimestamp

timestamptz

Instance details

Defined in Database.PostgreSQL.Simple.FromField

ParseTime UTCTime 
Instance details

Defined in Data.Time.Format.Parse

HasSqlEqualityCheck SqlSyntaxBuilder UTCTime 
Instance details

Defined in Database.Beam.Query.Ord

HasSqlEqualityCheck Expression UTCTime 
Instance details

Defined in Database.Beam.Query.Ord

HasSqlEqualityCheck PgExpressionSyntax UTCTime 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasSqlEqualityCheck PgExpressionSyntax UTCTimestamp 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasSqlQuantifiedEqualityCheck SqlSyntaxBuilder UTCTime 
Instance details

Defined in Database.Beam.Query.Ord

HasSqlQuantifiedEqualityCheck Expression UTCTime 
Instance details

Defined in Database.Beam.Query.Ord

HasSqlQuantifiedEqualityCheck PgExpressionSyntax UTCTime 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasSqlQuantifiedEqualityCheck PgExpressionSyntax UTCTimestamp 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasSqlValueSyntax Value UTCTime 
Instance details

Defined in Database.Beam.Backend.SQL.AST

HasSqlValueSyntax PgValueSyntax UTCTime 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasSqlValueSyntax PgValueSyntax UTCTimestamp 
Instance details

Defined in Database.Beam.Postgres.Syntax

FromBackendRow Postgres UTCTime 
Instance details

Defined in Database.Beam.Postgres.Types

FromBackendRow Postgres UTCTimestamp 
Instance details

Defined in Database.Beam.Postgres.Types

ToField (PGRange UTCTime) 
Instance details

Defined in Database.PostgreSQL.Simple.Range

ToField (PGRange UTCTimestamp) 
Instance details

Defined in Database.PostgreSQL.Simple.Range

data LocalTime #

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

Instances
Eq LocalTime 
Instance details

Defined in Data.Time.LocalTime.Internal.LocalTime

Data LocalTime 
Instance details

Defined in Data.Time.LocalTime.Internal.LocalTime

Methods

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

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

toConstr :: LocalTime -> Constr #

dataTypeOf :: LocalTime -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord LocalTime 
Instance details

Defined in Data.Time.LocalTime.Internal.LocalTime

Show LocalTime 
Instance details

Defined in Data.Time.LocalTime.Internal.LocalTime

FromJSON LocalTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey LocalTime 
Instance details

Defined in Data.Aeson.Types.FromJSON

NFData LocalTime 
Instance details

Defined in Data.Time.LocalTime.Internal.LocalTime

Methods

rnf :: LocalTime -> () #

FromField LocalTimestamp

timestamp

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField LocalTime

timestamp

Instance details

Defined in Database.PostgreSQL.Simple.FromField

ParseTime LocalTime 
Instance details

Defined in Data.Time.Format.Parse

HasSqlEqualityCheck SqlSyntaxBuilder LocalTime 
Instance details

Defined in Database.Beam.Query.Ord

HasSqlEqualityCheck Expression LocalTime 
Instance details

Defined in Database.Beam.Query.Ord

HasSqlEqualityCheck PgExpressionSyntax LocalTimestamp 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasSqlEqualityCheck PgExpressionSyntax LocalTime 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasSqlQuantifiedEqualityCheck SqlSyntaxBuilder LocalTime 
Instance details

Defined in Database.Beam.Query.Ord

HasSqlQuantifiedEqualityCheck Expression LocalTime 
Instance details

Defined in Database.Beam.Query.Ord

HasSqlQuantifiedEqualityCheck PgExpressionSyntax LocalTimestamp 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasSqlQuantifiedEqualityCheck PgExpressionSyntax LocalTime 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasSqlValueSyntax Value LocalTime 
Instance details

Defined in Database.Beam.Backend.SQL.AST

HasSqlValueSyntax PgValueSyntax LocalTimestamp 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasSqlValueSyntax PgValueSyntax LocalTime 
Instance details

Defined in Database.Beam.Postgres.Syntax

FromBackendRow Postgres LocalTimestamp 
Instance details

Defined in Database.Beam.Postgres.Types

FromBackendRow Postgres LocalTime 
Instance details

Defined in Database.Beam.Postgres.Types

HasDefaultSqlDataTypeConstraints PgColumnSchemaSyntax LocalTime 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasDefaultSqlDataType PgDataTypeSyntax LocalTime 
Instance details

Defined in Database.Beam.Postgres.Syntax

ToField (PGRange LocalTimestamp) 
Instance details

Defined in Database.PostgreSQL.Simple.Range

ToField (PGRange LocalTime) 
Instance details

Defined in Database.PostgreSQL.Simple.Range

data TimeOfDay #

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

Instances
Eq TimeOfDay 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeOfDay

Data TimeOfDay 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeOfDay

Methods

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

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

toConstr :: TimeOfDay -> Constr #

dataTypeOf :: TimeOfDay -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord TimeOfDay 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeOfDay

Show TimeOfDay 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeOfDay

FromJSON TimeOfDay 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey TimeOfDay 
Instance details

Defined in Data.Aeson.Types.FromJSON

NFData TimeOfDay 
Instance details

Defined in Data.Time.LocalTime.Internal.TimeOfDay

Methods

rnf :: TimeOfDay -> () #

FromField TimeOfDay

time

Instance details

Defined in Database.PostgreSQL.Simple.FromField

ParseTime TimeOfDay 
Instance details

Defined in Data.Time.Format.Parse

HasSqlEqualityCheck SqlSyntaxBuilder TimeOfDay 
Instance details

Defined in Database.Beam.Query.Ord

HasSqlEqualityCheck Expression TimeOfDay 
Instance details

Defined in Database.Beam.Query.Ord

HasSqlEqualityCheck PgExpressionSyntax TimeOfDay 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasSqlQuantifiedEqualityCheck SqlSyntaxBuilder TimeOfDay 
Instance details

Defined in Database.Beam.Query.Ord

HasSqlQuantifiedEqualityCheck Expression TimeOfDay 
Instance details

Defined in Database.Beam.Query.Ord

HasSqlQuantifiedEqualityCheck PgExpressionSyntax TimeOfDay 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasSqlValueSyntax Value TimeOfDay 
Instance details

Defined in Database.Beam.Backend.SQL.AST

HasSqlValueSyntax PgValueSyntax TimeOfDay 
Instance details

Defined in Database.Beam.Postgres.Syntax

FromBackendRow Postgres TimeOfDay 
Instance details

Defined in Database.Beam.Postgres.Types

ToField (PGRange TimeOfDay) 
Instance details

Defined in Database.PostgreSQL.Simple.Range

data Day #

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

Instances
Enum Day 
Instance details

Defined in Data.Time.Calendar.Days

Methods

succ :: Day -> Day #

pred :: Day -> Day #

toEnum :: Int -> Day #

fromEnum :: Day -> Int #

enumFrom :: Day -> [Day] #

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

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

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

Eq Day 
Instance details

Defined in Data.Time.Calendar.Days

Methods

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

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

Data Day 
Instance details

Defined in Data.Time.Calendar.Days

Methods

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

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

toConstr :: Day -> Constr #

dataTypeOf :: Day -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord Day 
Instance details

Defined in Data.Time.Calendar.Days

Methods

compare :: Day -> Day -> Ordering #

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

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

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

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

max :: Day -> Day -> Day #

min :: Day -> Day -> Day #

Ix Day 
Instance details

Defined in Data.Time.Calendar.Days

Methods

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

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

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

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

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

unsafeRangeSize :: (Day, Day) -> Int

FromJSON Day 
Instance details

Defined in Data.Aeson.Types.FromJSON

FromJSONKey Day 
Instance details

Defined in Data.Aeson.Types.FromJSON

NFData Day 
Instance details

Defined in Data.Time.Calendar.Days

Methods

rnf :: Day -> () #

FromField Date

date

Instance details

Defined in Database.PostgreSQL.Simple.FromField

FromField Day

date

Instance details

Defined in Database.PostgreSQL.Simple.FromField

ParseTime Day 
Instance details

Defined in Data.Time.Format.Parse

Methods

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

HasSqlEqualityCheck SqlSyntaxBuilder Day 
Instance details

Defined in Database.Beam.Query.Ord

HasSqlEqualityCheck Expression Day 
Instance details

Defined in Database.Beam.Query.Ord

HasSqlEqualityCheck PgExpressionSyntax Date 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasSqlEqualityCheck PgExpressionSyntax Day 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasSqlQuantifiedEqualityCheck SqlSyntaxBuilder Day 
Instance details

Defined in Database.Beam.Query.Ord

HasSqlQuantifiedEqualityCheck Expression Day 
Instance details

Defined in Database.Beam.Query.Ord

HasSqlQuantifiedEqualityCheck PgExpressionSyntax Date 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasSqlQuantifiedEqualityCheck PgExpressionSyntax Day 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasSqlValueSyntax Value Day 
Instance details

Defined in Database.Beam.Backend.SQL.AST

Methods

sqlValueSyntax :: Day -> Value #

HasSqlValueSyntax PgValueSyntax Date 
Instance details

Defined in Database.Beam.Postgres.Syntax

HasSqlValueSyntax PgValueSyntax Day 
Instance details

Defined in Database.Beam.Postgres.Syntax

FromBackendRow Postgres Date 
Instance details

Defined in Database.Beam.Postgres.Types

FromBackendRow Postgres Day 
Instance details

Defined in Database.Beam.Postgres.Types

ToField (PGRange Date) 
Instance details

Defined in Database.PostgreSQL.Simple.Range

Methods

toField :: PGRange Date -> Action #

ToField (PGRange Day) 
Instance details

Defined in Database.PostgreSQL.Simple.Range

Methods

toField :: PGRange Day -> Action #

Re-exports for the deriveGeneric plus deriveVinyl combination

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 is a safer alternative to the 'undefined :: a' idiom.

>>> Proxy :: Proxy (Void, Int -> Int)
Proxy

Proxy can even hold types of higher kinds,

>>> Proxy :: Proxy Either
Proxy
>>> Proxy :: Proxy Functor
Proxy
>>> Proxy :: Proxy complicatedStructure
Proxy

Constructors

Proxy 
Instances
Generic1 (Proxy :: k -> *) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep1 Proxy :: k -> * #

Methods

from1 :: Proxy a -> Rep1 Proxy a #

to1 :: Rep1 Proxy a -> Proxy a #

Monad (Proxy :: * -> *)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

(>>=) :: Proxy a -> (a -> Proxy b) -> Proxy b #

(>>) :: Proxy a -> Proxy b -> Proxy b #

return :: a -> Proxy a #

fail :: String -> Proxy a #

Functor (Proxy :: * -> *)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

fmap :: (a -> b) -> Proxy a -> Proxy b #

(<$) :: a -> Proxy b -> Proxy a #

Applicative (Proxy :: * -> *)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

pure :: a -> Proxy a #

(<*>) :: Proxy (a -> b) -> Proxy a -> Proxy b #

liftA2 :: (a -> b -> c) -> Proxy a -> Proxy b -> Proxy c #

(*>) :: Proxy a -> Proxy b -> Proxy b #

(<*) :: Proxy a -> Proxy b -> Proxy a #

Foldable (Proxy :: * -> *)

Since: base-4.7.0.0

Instance details

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 #

toList :: Proxy a -> [a] #

null :: Proxy a -> Bool #

length :: Proxy a -> Int #

elem :: Eq a => a -> Proxy a -> Bool #

maximum :: Ord a => Proxy a -> a #

minimum :: Ord a => Proxy a -> a #

sum :: Num a => Proxy a -> a #

product :: Num a => Proxy a -> a #

Traversable (Proxy :: * -> *)

Since: base-4.7.0.0

Instance details

Defined in Data.Traversable

Methods

traverse :: Applicative f => (a -> f b) -> Proxy a -> f (Proxy b) #

sequenceA :: Applicative f => Proxy (f a) -> f (Proxy a) #

mapM :: Monad m => (a -> m b) -> Proxy a -> m (Proxy b) #

sequence :: Monad m => Proxy (m a) -> m (Proxy a) #

Representable (Proxy :: * -> *) 
Instance details

Defined in Data.Functor.Rep

Associated Types

type Rep Proxy :: * #

Methods

tabulate :: (Rep Proxy -> a) -> Proxy a #

index :: Proxy a -> Rep Proxy -> a #

FromJSON1 (Proxy :: * -> *) 
Instance details

Defined in Data.Aeson.Types.FromJSON

Methods

liftParseJSON :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser (Proxy a) #

liftParseJSONList :: (Value -> Parser a) -> (Value -> Parser [a]) -> Value -> Parser [Proxy a] #

Alternative (Proxy :: * -> *)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

empty :: Proxy a #

(<|>) :: Proxy a -> Proxy a -> Proxy a #

some :: Proxy a -> Proxy [a] #

many :: Proxy a -> Proxy [a] #

MonadPlus (Proxy :: * -> *)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

mzero :: Proxy a #

mplus :: Proxy a -> Proxy a -> Proxy a #

Bounded (Proxy t) 
Instance details

Defined in Data.Proxy

Methods

minBound :: Proxy t #

maxBound :: Proxy t #

Enum (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

succ :: Proxy s -> Proxy s #

pred :: Proxy s -> Proxy s #

toEnum :: Int -> Proxy s #

fromEnum :: Proxy s -> Int #

enumFrom :: Proxy s -> [Proxy s] #

enumFromThen :: Proxy s -> Proxy s -> [Proxy s] #

enumFromTo :: Proxy s -> Proxy s -> [Proxy s] #

enumFromThenTo :: Proxy s -> Proxy s -> Proxy s -> [Proxy s] #

Eq (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

(==) :: Proxy s -> Proxy s -> Bool #

(/=) :: Proxy s -> Proxy s -> Bool #

Ord (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

compare :: Proxy s -> Proxy s -> Ordering #

(<) :: Proxy s -> Proxy s -> Bool #

(<=) :: Proxy s -> Proxy s -> Bool #

(>) :: Proxy s -> Proxy s -> Bool #

(>=) :: Proxy s -> Proxy s -> Bool #

max :: Proxy s -> Proxy s -> Proxy s #

min :: Proxy s -> Proxy s -> Proxy s #

Read (Proxy t)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Show (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

showsPrec :: Int -> Proxy s -> ShowS #

show :: Proxy s -> String #

showList :: [Proxy s] -> ShowS #

Ix (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

range :: (Proxy s, Proxy s) -> [Proxy s] #

index :: (Proxy s, Proxy s) -> Proxy s -> Int #

unsafeIndex :: (Proxy s, Proxy s) -> Proxy s -> Int

inRange :: (Proxy s, Proxy s) -> Proxy s -> Bool #

rangeSize :: (Proxy s, Proxy s) -> Int #

unsafeRangeSize :: (Proxy s, Proxy s) -> Int

Generic (Proxy t) 
Instance details

Defined in GHC.Generics

Associated Types

type Rep (Proxy t) :: * -> * #

Methods

from :: Proxy t -> Rep (Proxy t) x #

to :: Rep (Proxy t) x -> Proxy t #

Semigroup (Proxy s)

Since: base-4.9.0.0

Instance details

Defined in Data.Proxy

Methods

(<>) :: Proxy s -> Proxy s -> Proxy s #

sconcat :: NonEmpty (Proxy s) -> Proxy s #

stimes :: Integral b => b -> Proxy s -> Proxy s #

Monoid (Proxy s)

Since: base-4.7.0.0

Instance details

Defined in Data.Proxy

Methods

mempty :: Proxy s #

mappend :: Proxy s -> Proxy s -> Proxy s #

mconcat :: [Proxy s] -> Proxy s #

FromJSON (Proxy a) 
Instance details

Defined in Data.Aeson.Types.FromJSON

type Rep1 (Proxy :: k -> *) 
Instance details

Defined in GHC.Generics

type Rep1 (Proxy :: k -> *) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) (U1 :: k -> *))
type Rep (Proxy :: * -> *) 
Instance details

Defined in Data.Functor.Rep

type Rep (Proxy :: * -> *) = Void
type Rep (Proxy t) 
Instance details

Defined in GHC.Generics

type Rep (Proxy t) = D1 (MetaData "Proxy" "Data.Proxy" "base" False) (C1 (MetaCons "Proxy" PrefixI False) (U1 :: * -> *))
type Code (Proxy t) 
Instance details

Defined in Generics.SOP.Instances

type Code (Proxy t) = ([] :: [*]) ': ([] :: [[*]])
type DatatypeInfoOf (Proxy t) 
Instance details

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

Instances
Bounded Associativity 
Instance details

Defined in GHC.Generics

Enum Associativity 
Instance details

Defined in GHC.Generics

Eq Associativity 
Instance details

Defined in GHC.Generics

Ord Associativity 
Instance details

Defined in GHC.Generics

Read Associativity 
Instance details

Defined in GHC.Generics

Show Associativity 
Instance details

Defined in GHC.Generics

Ix Associativity 
Instance details

Defined in GHC.Generics

Generic Associativity 
Instance details

Defined in GHC.Generics

Associated Types

type Rep Associativity :: * -> * #

SingKind Associativity

Since: base-4.0.0.0

Instance details

Defined in GHC.Generics

Associated Types

type DemoteRep Associativity :: *

Methods

fromSing :: Sing a -> DemoteRep Associativity

SingI LeftAssociative

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing LeftAssociative

SingI RightAssociative

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing RightAssociative

SingI NotAssociative

Since: base-4.9.0.0

Instance details

Defined in GHC.Generics

Methods

sing :: Sing NotAssociative

type Rep Associativity 
Instance details

Defined in GHC.Generics

type Rep Associativity = D1 (MetaData "Associativity" "GHC.Generics" "base" False) (C1 (MetaCons "LeftAssociative" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "RightAssociative" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "NotAssociative" PrefixI False) (U1 :: * -> *)))
data Sing (a :: Associativity) 
Instance details

Defined in GHC.Generics

type DemoteRep Associativity 
Instance details

Defined in GHC.Generics

type DemoteRep Associativity = Associativity

type Rep a = SOP I (Code a) #

The (generic) representation of a datatype.

A datatype is isomorphic to the sum-of-products of its code. The isomorphism is witnessed by from and to from the Generic class.

type family Code a :: [[*]] #

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 
Instance details

Defined in Generics.SOP.Instances

type Code Bool = ([] :: [*]) ': (([] :: [*]) ': ([] :: [[*]]))
type Code Ordering 
Instance details

Defined in Generics.SOP.Instances

type Code Ordering = ([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': ([] :: [[*]])))
type Code () 
Instance details

Defined in Generics.SOP.Instances

type Code () = ([] :: [*]) ': ([] :: [[*]])
type Code DataRep 
Instance details

Defined in Generics.SOP.Instances

type Code DataRep = ([Constr] ': ([] :: [*])) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': ([] :: [[*]])))))
type Code ConstrRep 
Instance details

Defined in Generics.SOP.Instances

type Code ConstrRep = (ConIndex ': ([] :: [*])) ': ((Integer ': ([] :: [*])) ': ((Rational ': ([] :: [*])) ': ((Char ': ([] :: [*])) ': ([] :: [[*]]))))
type Code Fixity 
Instance details

Defined in Generics.SOP.Instances

type Code Fixity = ([] :: [*]) ': (([] :: [*]) ': ([] :: [[*]]))
type Code FormatAdjustment 
Instance details

Defined in Generics.SOP.Instances

type Code FormatAdjustment = ([] :: [*]) ': (([] :: [*]) ': ([] :: [[*]]))
type Code FormatSign 
Instance details

Defined in Generics.SOP.Instances

type Code FormatSign = ([] :: [*]) ': (([] :: [*]) ': ([] :: [[*]]))
type Code FieldFormat 
Instance details

Defined in Generics.SOP.Instances

type Code FieldFormat = (Maybe Int ': (Maybe Int ': (Maybe FormatAdjustment ': (Maybe FormatSign ': (Bool ': (String ': (Char ': ([] :: [*])))))))) ': ([] :: [[*]])
type Code FormatParse 
Instance details

Defined in Generics.SOP.Instances

type Code FormatParse = (String ': (Char ': (String ': ([] :: [*])))) ': ([] :: [[*]])
type Code Version 
Instance details

Defined in Generics.SOP.Instances

type Code Version = ([Int] ': ([String] ': ([] :: [*]))) ': ([] :: [[*]])
type Code PatternMatchFail 
Instance details

Defined in Generics.SOP.Instances

type Code PatternMatchFail = (String ': ([] :: [*])) ': ([] :: [[*]])
type Code RecSelError 
Instance details

Defined in Generics.SOP.Instances

type Code RecSelError = (String ': ([] :: [*])) ': ([] :: [[*]])
type Code RecConError 
Instance details

Defined in Generics.SOP.Instances

type Code RecConError = (String ': ([] :: [*])) ': ([] :: [[*]])
type Code RecUpdError 
Instance details

Defined in Generics.SOP.Instances

type Code RecUpdError = (String ': ([] :: [*])) ': ([] :: [[*]])
type Code NoMethodError 
Instance details

Defined in Generics.SOP.Instances

type Code NoMethodError = (String ': ([] :: [*])) ': ([] :: [[*]])
type Code NonTermination 
Instance details

Defined in Generics.SOP.Instances

type Code NonTermination = ([] :: [*]) ': ([] :: [[*]])
type Code NestedAtomically 
Instance details

Defined in Generics.SOP.Instances

type Code NestedAtomically = ([] :: [*]) ': ([] :: [[*]])
type Code Errno 
Instance details

Defined in Generics.SOP.Instances

type Code Errno = (CInt ': ([] :: [*])) ': ([] :: [[*]])
type Code BlockedIndefinitelyOnMVar 
Instance details

Defined in Generics.SOP.Instances

type Code BlockedIndefinitelyOnMVar = ([] :: [*]) ': ([] :: [[*]])
type Code BlockedIndefinitelyOnSTM 
Instance details

Defined in Generics.SOP.Instances

type Code BlockedIndefinitelyOnSTM = ([] :: [*]) ': ([] :: [[*]])
type Code Deadlock 
Instance details

Defined in Generics.SOP.Instances

type Code Deadlock = ([] :: [*]) ': ([] :: [[*]])
type Code AssertionFailed 
Instance details

Defined in Generics.SOP.Instances

type Code AssertionFailed = (String ': ([] :: [*])) ': ([] :: [[*]])
type Code AsyncException 
Instance details

Defined in Generics.SOP.Instances

type Code AsyncException = ([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': ([] :: [[*]]))))
type Code ArrayException 
Instance details

Defined in Generics.SOP.Instances

type Code ArrayException = (String ': ([] :: [*])) ': ((String ': ([] :: [*])) ': ([] :: [[*]]))
type Code ExitCode 
Instance details

Defined in Generics.SOP.Instances

type Code ExitCode = ([] :: [*]) ': ((Int ': ([] :: [*])) ': ([] :: [[*]]))
type Code BufferMode 
Instance details

Defined in Generics.SOP.Instances

type Code BufferMode = ([] :: [*]) ': (([] :: [*]) ': ((Maybe Int ': ([] :: [*])) ': ([] :: [[*]])))
type Code Newline 
Instance details

Defined in Generics.SOP.Instances

type Code Newline = ([] :: [*]) ': (([] :: [*]) ': ([] :: [[*]]))
type Code NewlineMode 
Instance details

Defined in Generics.SOP.Instances

type Code NewlineMode = (Newline ': (Newline ': ([] :: [*]))) ': ([] :: [[*]])
type Code SeekMode 
Instance details

Defined in Generics.SOP.Instances

type Code SeekMode = ([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': ([] :: [[*]])))
type Code MaskingState 
Instance details

Defined in Generics.SOP.Instances

type Code MaskingState = ([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': ([] :: [[*]])))
type Code IOException 
Instance details

Defined in Generics.SOP.Instances

type Code IOException = (Maybe Handle ': (IOErrorType ': (String ': (String ': (Maybe CInt ': (Maybe FilePath ': ([] :: [*]))))))) ': ([] :: [[*]])
type Code ErrorCall 
Instance details

Defined in Generics.SOP.Instances

type Code ErrorCall = (String ': (String ': ([] :: [*]))) ': ([] :: [[*]])
type Code ArithException 
Instance details

Defined in Generics.SOP.Instances

type Code ArithException = ([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': ([] :: [[*]]))))))
type Code All 
Instance details

Defined in Generics.SOP.Instances

type Code All = (Bool ': ([] :: [*])) ': ([] :: [[*]])
type Code Any 
Instance details

Defined in Generics.SOP.Instances

type Code Any = (Bool ': ([] :: [*])) ': ([] :: [[*]])
type Code CChar 
Instance details

Defined in Generics.SOP.Instances

type Code CChar = (Int8 ': ([] :: [*])) ': ([] :: [[*]])
type Code CSChar 
Instance details

Defined in Generics.SOP.Instances

type Code CSChar = (Int8 ': ([] :: [*])) ': ([] :: [[*]])
type Code CUChar 
Instance details

Defined in Generics.SOP.Instances

type Code CUChar = (Word8 ': ([] :: [*])) ': ([] :: [[*]])
type Code CShort 
Instance details

Defined in Generics.SOP.Instances

type Code CShort = (Int16 ': ([] :: [*])) ': ([] :: [[*]])
type Code CUShort 
Instance details

Defined in Generics.SOP.Instances

type Code CUShort = (Word16 ': ([] :: [*])) ': ([] :: [[*]])
type Code CInt 
Instance details

Defined in Generics.SOP.Instances

type Code CInt = (Int32 ': ([] :: [*])) ': ([] :: [[*]])
type Code CUInt 
Instance details

Defined in Generics.SOP.Instances

type Code CUInt = (Word32 ': ([] :: [*])) ': ([] :: [[*]])
type Code CLong 
Instance details

Defined in Generics.SOP.Instances

type Code CLong = (Int64 ': ([] :: [*])) ': ([] :: [[*]])
type Code CULong 
Instance details

Defined in Generics.SOP.Instances

type Code CULong = (Word64 ': ([] :: [*])) ': ([] :: [[*]])
type Code CLLong 
Instance details

Defined in Generics.SOP.Instances

type Code CLLong = (Int64 ': ([] :: [*])) ': ([] :: [[*]])
type Code CULLong 
Instance details

Defined in Generics.SOP.Instances

type Code CULLong = (Word64 ': ([] :: [*])) ': ([] :: [[*]])
type Code CFloat 
Instance details

Defined in Generics.SOP.Instances

type Code CFloat = (Float ': ([] :: [*])) ': ([] :: [[*]])
type Code CDouble 
Instance details

Defined in Generics.SOP.Instances

type Code CDouble = (Double ': ([] :: [*])) ': ([] :: [[*]])
type Code CPtrdiff 
Instance details

Defined in Generics.SOP.Instances

type Code CPtrdiff = (Int64 ': ([] :: [*])) ': ([] :: [[*]])
type Code CSize 
Instance details

Defined in Generics.SOP.Instances

type Code CSize = (Word64 ': ([] :: [*])) ': ([] :: [[*]])
type Code CWchar 
Instance details

Defined in Generics.SOP.Instances

type Code CWchar = (Int32 ': ([] :: [*])) ': ([] :: [[*]])
type Code CSigAtomic 
Instance details

Defined in Generics.SOP.Instances

type Code CSigAtomic = (Int32 ': ([] :: [*])) ': ([] :: [[*]])
type Code CClock 
Instance details

Defined in Generics.SOP.Instances

type Code CClock = (Int64 ': ([] :: [*])) ': ([] :: [[*]])
type Code CTime 
Instance details

Defined in Generics.SOP.Instances

type Code CTime = (Int64 ': ([] :: [*])) ': ([] :: [[*]])
type Code CUSeconds 
Instance details

Defined in Generics.SOP.Instances

type Code CUSeconds = (Word32 ': ([] :: [*])) ': ([] :: [[*]])
type Code CSUSeconds 
Instance details

Defined in Generics.SOP.Instances

type Code CSUSeconds = (Int64 ': ([] :: [*])) ': ([] :: [[*]])
type Code CIntPtr 
Instance details

Defined in Generics.SOP.Instances

type Code CIntPtr = (Int64 ': ([] :: [*])) ': ([] :: [[*]])
type Code CUIntPtr 
Instance details

Defined in Generics.SOP.Instances

type Code CUIntPtr = (Word64 ': ([] :: [*])) ': ([] :: [[*]])
type Code CIntMax 
Instance details

Defined in Generics.SOP.Instances

type Code CIntMax = (Int64 ': ([] :: [*])) ': ([] :: [[*]])
type Code CUIntMax 
Instance details

Defined in Generics.SOP.Instances

type Code CUIntMax = (Word64 ': ([] :: [*])) ': ([] :: [[*]])
type Code IOMode 
Instance details

Defined in Generics.SOP.Instances

type Code IOMode = ([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': ([] :: [[*]]))))
type Code Lexeme 
Instance details

Defined in Generics.SOP.Instances

type Code Lexeme = (Char ': ([] :: [*])) ': ((String ': ([] :: [*])) ': ((String ': ([] :: [*])) ': ((String ': ([] :: [*])) ': ((String ': ([] :: [*])) ': ((Number ': ([] :: [*])) ': (([] :: [*]) ': ([] :: [[*]])))))))
type Code Number 
Instance details

Defined in Generics.SOP.Instances

type Code Number = (Int ': (Digits ': ([] :: [*]))) ': ((Digits ': (Maybe Digits ': (Maybe Integer ': ([] :: [*])))) ': ([] :: [[*]]))
type Code GeneralCategory 
Instance details

Defined in Generics.SOP.Instances

type Code GeneralCategory = ([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': (([] :: [*]) ': ([] :: [[*]]))))))))))))))))))))))))))))))
type Code [a] 
Instance details

Defined in Generics.SOP.Instances

type Code [a] = ([] :: [*]) ': ((a ': ([a] ': ([] :: [*]))) ': ([] :: [[*]]))
type Code (Maybe a) 
Instance details

Defined in Generics.SOP.Instances

type Code (Maybe a) = ([] :: [*]) ': ((a ': ([] :: [*])) ': ([] :: [[*]]))
type Code (Complex a) 
Instance details

Defined in Generics.SOP.Instances

type Code (Complex a) = (a ': (a ': ([] :: [*]))) ': ([] :: [[*]])
type Code (Fixed a) 
Instance details

Defined in Generics.SOP.Instances

type Code (Fixed a) = (Integer ': ([] :: [*])) ': ([] :: [[*]])
type Code (ArgOrder a) 
Instance details

Defined in Generics.SOP.Instances

type Code (ArgOrder a) = ([] :: [*]) ': (([] :: [*]) ': (((String -> a) ': ([] :: [*])) ': ([] :: [[*]])))
type Code (OptDescr a) 
Instance details

Defined in Generics.SOP.Instances

type Code (OptDescr a) = ([Char] ': ([String] ': (ArgDescr a ': (String ': ([] :: [*]))))) ': ([] :: [[*]])
type Code (ArgDescr a) 
Instance details

Defined in Generics.SOP.Instances

type Code (ArgDescr a) = (a ': ([] :: [*])) ': (((String -> a) ': (String ': ([] :: [*]))) ': (((Maybe String -> a) ': (String ': ([] :: [*]))) ': ([] :: [[*]])))
type Code (First a) 
Instance details

Defined in Generics.SOP.Instances

type Code (First a) = (Maybe a ': ([] :: [*])) ': ([] :: [[*]])
type Code (Last a) 
Instance details

Defined in Generics.SOP.Instances

type Code (Last a) = (Maybe a ': ([] :: [*])) ': ([] :: [[*]])
type Code (Dual a) 
Instance details

Defined in Generics.SOP.Instances

type Code (Dual a) = (a ': ([] :: [*])) ': ([] :: [[*]])
type Code (Endo a) 
Instance details

Defined in Generics.SOP.Instances

type Code (Endo a) = ((a -> a) ': ([] :: [*])) ': ([] :: [[*]])
type Code (Sum a) 
Instance details

Defined in Generics.SOP.Instances

type Code (Sum a) = (a ': ([] :: [*])) ': ([] :: [[*]])
type Code (Product a) 
Instance details

Defined in Generics.SOP.Instances

type Code (Product a) = (a ': ([] :: [*])) ': ([] :: [[*]])
type Code (Down a) 
Instance details

Defined in Generics.SOP.Instances

type Code (Down a) = (a ': ([] :: [*])) ': ([] :: [[*]])
type Code (I a) 
Instance details

Defined in Generics.SOP.Instances

type Code (I a) = (a ': ([] :: [*])) ': ([] :: [[*]])
type Code (Either a b) 
Instance details

Defined in Generics.SOP.Instances

type Code (Either a b) = (a ': ([] :: [*])) ': ((b ': ([] :: [*])) ': ([] :: [[*]]))
type Code (a, b) 
Instance details

Defined in Generics.SOP.Instances

type Code (a, b) = (a ': (b ': ([] :: [*]))) ': ([] :: [[*]])
type Code (Proxy t) 
Instance details

Defined in Generics.SOP.Instances

type Code (Proxy t) = ([] :: [*]) ': ([] :: [[*]])
type Code (a, b, c) 
Instance details

Defined in Generics.SOP.Instances

type Code (a, b, c) = (a ': (b ': (c ': ([] :: [*])))) ': ([] :: [[*]])
type Code (K a b) 
Instance details

Defined in Generics.SOP.Instances

type Code (K a b) = (a ': ([] :: [*])) ': ([] :: [[*]])
type Code (a, b, c, d) 
Instance details

Defined in Generics.SOP.Instances

type Code (a, b, c, d) = (a ': (b ': (c ': (d ': ([] :: [*]))))) ': ([] :: [[*]])
type Code (a, b, c, d, e) 
Instance details

Defined in Generics.SOP.Instances

type Code (a, b, c, d, e) = (a ': (b ': (c ': (d ': (e ': ([] :: [*])))))) ': ([] :: [[*]])
type Code ((f :.: g) p) 
Instance details

Defined in Generics.SOP.Instances

type Code ((f :.: g) p) = (f (g p) ': ([] :: [*])) ': ([] :: [[*]])
type Code (a, b, c, d, e, f) 
Instance details

Defined in Generics.SOP.Instances

type Code (a, b, c, d, e, f) = (a ': (b ': (c ': (d ': (e ': (f ': ([] :: [*]))))))) ': ([] :: [[*]])
type Code (a, b, c, d, e, f, g) 
Instance details

Defined in Generics.SOP.Instances

type Code (a, b, c, d, e, f, g) = (a ': (b ': (c ': (d ': (e ': (f ': (g ': ([] :: [*])))))))) ': ([] :: [[*]])
type Code (a, b, c, d, e, f, g, h) 
Instance details

Defined in Generics.SOP.Instances

type Code (a, b, c, d, e, f, g, h) = (a ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': ([] :: [*]))))))))) ': ([] :: [[*]])
type Code (a, b, c, d, e, f, g, h, i) 
Instance details

Defined in Generics.SOP.Instances

type Code (a, b, c, d, e, f, g, h, i) = (a ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': (i ': ([] :: [*])))))))))) ': ([] :: [[*]])
type Code (a, b, c, d, e, f, g, h, i, j) 
Instance details

Defined in Generics.SOP.Instances

type Code (a, b, c, d, e, f, g, h, i, j) = (a ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': (i ': (j ': ([] :: [*]))))))))))) ': ([] :: [[*]])
type Code (a, b, c, d, e, f, g, h, i, j, k) 
Instance details

Defined in Generics.SOP.Instances

type Code (a, b, c, d, e, f, g, h, i, j, k) = (a ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': (i ': (j ': (k ': ([] :: [*])))))))))))) ': ([] :: [[*]])
type Code (a, b, c, d, e, f, g, h, i, j, k, l) 
Instance details

Defined in Generics.SOP.Instances

type Code (a, b, c, d, e, f, g, h, i, j, k, l) = (a ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': (i ': (j ': (k ': (l ': ([] :: [*]))))))))))))) ': ([] :: [[*]])
type Code (a, b, c, d, e, f, g, h, i, j, k, l, m) 
Instance details

Defined in Generics.SOP.Instances

type Code (a, b, c, d, e, f, g, h, i, j, k, l, m) = (a ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': (i ': (j ': (k ': (l ': (m ': ([] :: [*])))))))))))))) ': ([] :: [[*]])
type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n) 
Instance details

Defined in Generics.SOP.Instances

type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n) = (a ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': (i ': (j ': (k ': (l ': (m ': (n ': ([] :: [*]))))))))))))))) ': ([] :: [[*]])
type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) 
Instance details

Defined in Generics.SOP.Instances

type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o) = (a ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': (i ': (j ': (k ': (l ': (m ': (n ': (o ': ([] :: [*])))))))))))))))) ': ([] :: [[*]])
type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) 
Instance details

Defined in Generics.SOP.Instances

type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p) = (a ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': (i ': (j ': (k ': (l ': (m ': (n ': (o ': (p ': ([] :: [*]))))))))))))))))) ': ([] :: [[*]])
type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) 
Instance details

Defined in Generics.SOP.Instances

type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q) = (a ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': (i ': (j ': (k ': (l ': (m ': (n ': (o ': (p ': (q ': ([] :: [*])))))))))))))))))) ': ([] :: [[*]])
type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r) 
Instance details

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) = (a ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': (i ': (j ': (k ': (l ': (m ': (n ': (o ': (p ': (q ': (r ': ([] :: [*]))))))))))))))))))) ': ([] :: [[*]])
type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s) 
Instance details

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) = (a ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': (i ': (j ': (k ': (l ': (m ': (n ': (o ': (p ': (q ': (r ': (s ': ([] :: [*])))))))))))))))))))) ': ([] :: [[*]])
type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t) 
Instance details

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) = (a ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': (i ': (j ': (k ': (l ': (m ': (n ': (o ': (p ': (q ': (r ': (s ': (t ': ([] :: [*]))))))))))))))))))))) ': ([] :: [[*]])
type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u) 
Instance details

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) = (a ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': (i ': (j ': (k ': (l ': (m ': (n ': (o ': (p ': (q ': (r ': (s ': (t ': (u ': ([] :: [*])))))))))))))))))))))) ': ([] :: [[*]])
type Code (a, b, c, d, e, f, g, h, i, j, k, l, m, n, o, p, q, r, s, t, u, v) 
Instance details

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) = (a ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': (i ': (j ': (k ': (l ': (m ': (n ': (o ': (p ': (q ': (r ': (s ': (t ': (u ': (v ': ([] :: [*]))))))))))))))))))))))) ': ([] :: [[*]])
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) 
Instance details

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) = (a ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': (i ': (j ': (k ': (l ': (m ': (n ': (o ': (p ': (q ': (r ': (s ': (t ': (u ': (v ': (w ': ([] :: [*])))))))))))))))))))))))) ': ([] :: [[*]])
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) 
Instance details

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) = (a ': (b ': (c ': (d ': (e ': (f ': (g ': (h ': (i ': (j ': (k ': (l ': (m ': (n ': (o ': (p ': (q ': (r ': (s ': (t ': (u ': (v ': (w ': (x ': ([] :: [*]))))))))))))))))))))))))) ': ([] :: [[*]])
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) 
Instance details

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) = (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 ': ([] :: [*])))))))))))))))))))))))))) ': ([] :: [[*]])
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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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) 
Instance details

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 ': ([] :: [*]))))))))))))))))))))))))))))))) ': ([] :: [[*]])

from :: Generic a => a -> Rep a #

Converts from a value to its structural representation.

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.

Associated Types

type DatatypeInfoOf a :: DatatypeInfo #

Type-level datatype info

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 c contains the information about a datatype that is not contained in Code c. This information consists primarily of the names of the datatype, its constructors, and possibly its record selectors.

The constructor indicates whether the datatype has been declared using newtype or not.

Constructors

ADT :: DatatypeInfo a 
Newtype :: DatatypeInfo ((x ': ([] :: [*])) ': ([] :: [[*]])) 

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 

data FieldInfo a #

For records, this functor maps the component to its selector name.

Constructors

FieldInfo FieldName 
Instances
Functor FieldInfo 
Instance details

Defined in Generics.SOP.Metadata

Methods

fmap :: (a -> b) -> FieldInfo a -> FieldInfo b #

(<$) :: a -> FieldInfo b -> FieldInfo a #

Eq (FieldInfo a) 
Instance details

Defined in Generics.SOP.Metadata

Methods

(==) :: FieldInfo a -> FieldInfo a -> Bool #

(/=) :: FieldInfo a -> FieldInfo a -> Bool #

Ord (FieldInfo a) 
Instance details

Defined in Generics.SOP.Metadata

Show (FieldInfo a) 
Instance details

Defined in Generics.SOP.Metadata

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.

type FieldName = String #

The name of a field / record selector.

type Fixity = Int #

The fixity of an infix constructor.

ccompare_SOP #

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

compare_SOP #

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

ccompare_NS #

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

compare_NS #

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.

unSOP :: SOP f xss -> NS (NP f) xss #

Unwrap a sum of products.

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, the result is a homogeneous choice type, where the contents of the type-level list are ignored, but its length specifies the number of options.

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 ]

Constructors

Z :: NS a (x ': xs) 
S :: NS a (x ': xs) 
Instances
HTrans (NS :: (k1 -> *) -> [k1] -> *) (NS :: (k2 -> *) -> [k2] -> *) 
Instance details

Defined in Generics.SOP.NS

Methods

htrans :: AllZipN (Prod NS) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> NS f xs -> NS g ys #

hcoerce :: (AllZipN (Prod NS) (LiftedCoercible f g) xs ys, HTrans NS NS) => NS f xs -> NS g ys #

HAp (NS :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NS

Methods

hap :: Prod NS (f -.-> g) xs -> NS f xs -> NS g xs #

HCollapse (NS :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NS

Methods

hcollapse :: SListIN NS xs => NS (K a) xs -> CollapseTo NS a #

HTraverse_ (NS :: (k -> *) -> [k] -> *) 
Instance details

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] -> *) 
Instance details

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] -> *) 
Instance details

Defined in Generics.SOP.NS

Methods

hindex :: NS f xs -> Int #

HApInjs (NS :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NS

Methods

hapInjs :: SListIN NS xs => Prod NS f xs -> [NS f xs] #

HExpand (NS :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NS

Methods

hexpand :: SListIN (Prod NS) xs => (forall (x :: k0). f x) -> NS f xs -> Prod NS f xs #

hcexpand :: AllN (Prod NS) c xs => proxy c -> (forall (x :: k0). c x => f x) -> NS f xs -> Prod NS f xs #

All (Compose Eq f) xs => Eq (NS f xs) 
Instance details

Defined in Generics.SOP.NS

Methods

(==) :: NS f xs -> NS f xs -> Bool #

(/=) :: NS f xs -> NS f xs -> Bool #

(All (Compose Eq f) xs, All (Compose Ord f) xs) => Ord (NS f xs) 
Instance details

Defined in Generics.SOP.NS

Methods

compare :: NS f xs -> NS f xs -> Ordering #

(<) :: NS f xs -> NS f xs -> Bool #

(<=) :: NS f xs -> NS f xs -> Bool #

(>) :: NS f xs -> NS f xs -> Bool #

(>=) :: NS f xs -> NS f xs -> Bool #

max :: NS f xs -> NS f xs -> NS f xs #

min :: NS f xs -> NS f xs -> NS f xs #

All (Compose Show f) xs => Show (NS f xs) 
Instance details

Defined in Generics.SOP.NS

Methods

showsPrec :: Int -> NS f xs -> ShowS #

show :: NS f xs -> String #

showList :: [NS f xs] -> ShowS #

All (Compose NFData f) xs => NFData (NS f xs)

Since: generics-sop-0.2.5.0

Instance details

Defined in Generics.SOP.NS

Methods

rnf :: NS f xs -> () #

type Same (NS :: (k1 -> *) -> [k1] -> *) 
Instance details

Defined in Generics.SOP.NS

type Same (NS :: (k1 -> *) -> [k1] -> *) = (NS :: (k2 -> *) -> [k2] -> *)
type Prod (NS :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NS

type Prod (NS :: (k -> *) -> [k] -> *) = (NP :: (k -> *) -> [k] -> *)
type SListIN (NS :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NS

type SListIN (NS :: (k -> *) -> [k] -> *) = (SListI :: [k] -> Constraint)
type CollapseTo (NS :: (k -> *) -> [k] -> *) a 
Instance details

Defined in Generics.SOP.NS

type CollapseTo (NS :: (k -> *) -> [k] -> *) a = a
type AllN (NS :: (k -> *) -> [k] -> *) (c :: k -> Constraint) 
Instance details

Defined in Generics.SOP.NS

type AllN (NS :: (k -> *) -> [k] -> *) (c :: k -> Constraint) = All c

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 reflects the structure of a normal Haskell datatype. The sum structure represents the choice between the different constructors, the product structure represents the arguments of each constructor.

Constructors

SOP (NS (NP f) xss) 
Instances
HTrans (SOP :: (k1 -> *) -> [[k1]] -> *) (SOP :: (k2 -> *) -> [[k2]] -> *) 
Instance details

Defined in Generics.SOP.NS

Methods

htrans :: AllZipN (Prod SOP) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> SOP f xs -> SOP g ys #

hcoerce :: (AllZipN (Prod SOP) (LiftedCoercible f g) xs ys, HTrans SOP SOP) => SOP f xs -> SOP g ys #

HAp (SOP :: (k -> *) -> [[k]] -> *) 
Instance details

Defined in Generics.SOP.NS

Methods

hap :: Prod SOP (f -.-> g) xs -> SOP f xs -> SOP g xs #

HCollapse (SOP :: (k -> *) -> [[k]] -> *) 
Instance details

Defined in Generics.SOP.NS

Methods

hcollapse :: SListIN SOP xs => SOP (K a) xs -> CollapseTo SOP a #

HTraverse_ (SOP :: (k -> *) -> [[k]] -> *) 
Instance details

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]] -> *) 
Instance details

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]] -> *) 
Instance details

Defined in Generics.SOP.NS

Methods

hindex :: SOP f xs -> Int #

HApInjs (SOP :: (k -> *) -> [[k]] -> *) 
Instance details

Defined in Generics.SOP.NS

Methods

hapInjs :: SListIN SOP xs => Prod SOP f xs -> [SOP f xs] #

HExpand (SOP :: (k -> *) -> [[k]] -> *) 
Instance details

Defined in Generics.SOP.NS

Methods

hexpand :: SListIN (Prod SOP) xs => (forall (x :: k0). f x) -> SOP f xs -> Prod SOP f xs #

hcexpand :: AllN (Prod SOP) c xs => proxy c -> (forall (x :: k0). c x => f x) -> SOP f xs -> Prod SOP f xs #

Eq (NS (NP f) xss) => Eq (SOP f xss) 
Instance details

Defined in Generics.SOP.NS

Methods

(==) :: SOP f xss -> SOP f xss -> Bool #

(/=) :: SOP f xss -> SOP f xss -> Bool #

Ord (NS (NP f) xss) => Ord (SOP f xss) 
Instance details

Defined in Generics.SOP.NS

Methods

compare :: SOP f xss -> SOP f xss -> Ordering #

(<) :: SOP f xss -> SOP f xss -> Bool #

(<=) :: SOP f xss -> SOP f xss -> Bool #

(>) :: SOP f xss -> SOP f xss -> Bool #

(>=) :: SOP f xss -> SOP f xss -> Bool #

max :: SOP f xss -> SOP f xss -> SOP f xss #

min :: SOP f xss -> SOP f xss -> SOP f xss #

Show (NS (NP f) xss) => Show (SOP f xss) 
Instance details

Defined in Generics.SOP.NS

Methods

showsPrec :: Int -> SOP f xss -> ShowS #

show :: SOP f xss -> String #

showList :: [SOP f xss] -> ShowS #

NFData (NS (NP f) xss) => NFData (SOP f xss)

Since: generics-sop-0.2.5.0

Instance details

Defined in Generics.SOP.NS

Methods

rnf :: SOP f xss -> () #

type Same (SOP :: (k1 -> *) -> [[k1]] -> *) 
Instance details

Defined in Generics.SOP.NS

type Same (SOP :: (k1 -> *) -> [[k1]] -> *) = (SOP :: (k2 -> *) -> [[k2]] -> *)
type Prod (SOP :: (k -> *) -> [[k]] -> *) 
Instance details

Defined in Generics.SOP.NS

type Prod (SOP :: (k -> *) -> [[k]] -> *) = (POP :: (k -> *) -> [[k]] -> *)
type SListIN (SOP :: (k -> *) -> [[k]] -> *) 
Instance details

Defined in Generics.SOP.NS

type SListIN (SOP :: (k -> *) -> [[k]] -> *) = (SListI2 :: [[k]] -> Constraint)
type CollapseTo (SOP :: (k -> *) -> [[k]] -> *) a 
Instance details

Defined in Generics.SOP.NS

type CollapseTo (SOP :: (k -> *) -> [[k]] -> *) a = [a]
type AllN (SOP :: (k -> *) -> [[k]] -> *) (c :: k -> Constraint) 
Instance details

Defined in Generics.SOP.NS

type AllN (SOP :: (k -> *) -> [[k]] -> *) (c :: k -> Constraint) = All2 c

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_NP p ` hap ` xs

Instances:

hcliftA' :: All2 c xss => proxy c -> (forall xs. All c xs => f xs -> f' xs) -> NP f xss -> NP f' xss
hcliftA' :: All2 c xss => proxy c -> (forall xs. All c xs => f xs -> f' xs) -> NS f xss -> NS f' 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.

tl :: NP f (x ': xs) -> NP f xs #

Obtain the tail of an n-ary product.

Since: generics-sop-0.2.1.0

hd :: NP f (x ': xs) -> f x #

Obtain the head of an n-ary product.

Since: generics-sop-0.2.1.0

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.

unPOP :: POP f xss -> NP (NP f) xss #

Unwrap a product of products.

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, the product becomes a homogeneous list, where the contents of the type-level list are ignored, but its length still specifies the number of elements.

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 ]

Constructors

Nil :: NP a ([] :: [k]) 
(:*) :: NP a (x ': xs) infixr 5 
Instances
HTrans (NP :: (k1 -> *) -> [k1] -> *) (NP :: (k2 -> *) -> [k2] -> *) 
Instance details

Defined in Generics.SOP.NP

Methods

htrans :: AllZipN (Prod NP) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> NP f xs -> NP g ys #

hcoerce :: (AllZipN (Prod NP) (LiftedCoercible f g) xs ys, HTrans NP NP) => NP f xs -> NP g ys #

HPure (NP :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NP

Methods

hpure :: SListIN NP xs => (forall (a :: k0). f a) -> NP f xs #

hcpure :: AllN NP c xs => proxy c -> (forall (a :: k0). c a => f a) -> NP f xs #

HAp (NP :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NP

Methods

hap :: Prod NP (f -.-> g) xs -> NP f xs -> NP g xs #

HCollapse (NP :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NP

Methods

hcollapse :: SListIN NP xs => NP (K a) xs -> CollapseTo NP a #

HTraverse_ (NP :: (k -> *) -> [k] -> *) 
Instance details

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] -> *) 
Instance details

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) 
Instance details

Defined in Generics.SOP.NP

Methods

(==) :: NP f xs -> NP f xs -> Bool #

(/=) :: NP f xs -> NP f xs -> Bool #

(All (Compose Eq f) xs, All (Compose Ord f) xs) => Ord (NP f xs) 
Instance details

Defined in Generics.SOP.NP

Methods

compare :: NP f xs -> NP f xs -> Ordering #

(<) :: NP f xs -> NP f xs -> Bool #

(<=) :: NP f xs -> NP f xs -> Bool #

(>) :: NP f xs -> NP f xs -> Bool #

(>=) :: NP f xs -> NP f xs -> Bool #

max :: NP f xs -> NP f xs -> NP f xs #

min :: NP f xs -> NP f xs -> NP f xs #

All (Compose Show f) xs => Show (NP f xs) 
Instance details

Defined in Generics.SOP.NP

Methods

showsPrec :: Int -> NP f xs -> ShowS #

show :: NP f xs -> String #

showList :: [NP f xs] -> ShowS #

All (Compose NFData f) xs => NFData (NP f xs)

Since: generics-sop-0.2.5.0

Instance details

Defined in Generics.SOP.NP

Methods

rnf :: NP f xs -> () #

type AllZipN (NP :: (k -> *) -> [k] -> *) (c :: a -> b -> Constraint) 
Instance details

Defined in Generics.SOP.NP

type AllZipN (NP :: (k -> *) -> [k] -> *) (c :: a -> b -> Constraint) = AllZip c
type Same (NP :: (k1 -> *) -> [k1] -> *) 
Instance details

Defined in Generics.SOP.NP

type Same (NP :: (k1 -> *) -> [k1] -> *) = (NP :: (k2 -> *) -> [k2] -> *)
type Prod (NP :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NP

type Prod (NP :: (k -> *) -> [k] -> *) = (NP :: (k -> *) -> [k] -> *)
type UnProd (NP :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NS

type UnProd (NP :: (k -> *) -> [k] -> *) = (NS :: (k -> *) -> [k] -> *)
type SListIN (NP :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NP

type SListIN (NP :: (k -> *) -> [k] -> *) = (SListI :: [k] -> Constraint)
type CollapseTo (NP :: (k -> *) -> [k] -> *) a 
Instance details

Defined in Generics.SOP.NP

type CollapseTo (NP :: (k -> *) -> [k] -> *) a = [a]
type AllN (NP :: (k -> *) -> [k] -> *) (c :: k -> Constraint) 
Instance details

Defined in Generics.SOP.NP

type AllN (NP :: (k -> *) -> [k] -> *) (c :: k -> Constraint) = All c

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.

Constructors

POP (NP (NP f) xss) 
Instances
HTrans (POP :: (k1 -> *) -> [[k1]] -> *) (POP :: (k2 -> *) -> [[k2]] -> *) 
Instance details

Defined in Generics.SOP.NP

Methods

htrans :: AllZipN (Prod POP) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> POP f xs -> POP g ys #

hcoerce :: (AllZipN (Prod POP) (LiftedCoercible f g) xs ys, HTrans POP POP) => POP f xs -> POP g ys #

HPure (POP :: (k -> *) -> [[k]] -> *) 
Instance details

Defined in Generics.SOP.NP

Methods

hpure :: SListIN POP xs => (forall (a :: k0). f a) -> POP f xs #

hcpure :: AllN POP c xs => proxy c -> (forall (a :: k0). c a => f a) -> POP f xs #

HAp (POP :: (k -> *) -> [[k]] -> *) 
Instance details

Defined in Generics.SOP.NP

Methods

hap :: Prod POP (f -.-> g) xs -> POP f xs -> POP g xs #

HCollapse (POP :: (k -> *) -> [[k]] -> *) 
Instance details

Defined in Generics.SOP.NP

Methods

hcollapse :: SListIN POP xs => POP (K a) xs -> CollapseTo POP a #

HTraverse_ (POP :: (k -> *) -> [[k]] -> *) 
Instance details

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]] -> *) 
Instance details

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) 
Instance details

Defined in Generics.SOP.NP

Methods

(==) :: POP f xss -> POP f xss -> Bool #

(/=) :: POP f xss -> POP f xss -> Bool #

Ord (NP (NP f) xss) => Ord (POP f xss) 
Instance details

Defined in Generics.SOP.NP

Methods

compare :: POP f xss -> POP f xss -> Ordering #

(<) :: POP f xss -> POP f xss -> Bool #

(<=) :: POP f xss -> POP f xss -> Bool #

(>) :: POP f xss -> POP f xss -> Bool #

(>=) :: POP f xss -> POP f xss -> Bool #

max :: POP f xss -> POP f xss -> POP f xss #

min :: POP f xss -> POP f xss -> POP f xss #

Show (NP (NP f) xss) => Show (POP f xss) 
Instance details

Defined in Generics.SOP.NP

Methods

showsPrec :: Int -> POP f xss -> ShowS #

show :: POP f xss -> String #

showList :: [POP f xss] -> ShowS #

NFData (NP (NP f) xss) => NFData (POP f xss)

Since: generics-sop-0.2.5.0

Instance details

Defined in Generics.SOP.NP

Methods

rnf :: POP f xss -> () #

type AllZipN (POP :: (k -> *) -> [[k]] -> *) (c :: a -> b -> Constraint) 
Instance details

Defined in Generics.SOP.NP

type AllZipN (POP :: (k -> *) -> [[k]] -> *) (c :: a -> b -> Constraint) = AllZip2 c
type Same (POP :: (k1 -> *) -> [[k1]] -> *) 
Instance details

Defined in Generics.SOP.NP

type Same (POP :: (k1 -> *) -> [[k1]] -> *) = (POP :: (k2 -> *) -> [[k2]] -> *)
type Prod (POP :: (k -> *) -> [[k]] -> *) 
Instance details

Defined in Generics.SOP.NP

type Prod (POP :: (k -> *) -> [[k]] -> *) = (POP :: (k -> *) -> [[k]] -> *)
type UnProd (POP :: (k -> *) -> [[k]] -> *) 
Instance details

Defined in Generics.SOP.NS

type UnProd (POP :: (k -> *) -> [[k]] -> *) = (SOP :: (k -> *) -> [[k]] -> *)
type SListIN (POP :: (k -> *) -> [[k]] -> *) 
Instance details

Defined in Generics.SOP.NP

type SListIN (POP :: (k -> *) -> [[k]] -> *) = (SListI2 :: [[k]] -> Constraint)
type CollapseTo (POP :: (k -> *) -> [[k]] -> *) a 
Instance details

Defined in Generics.SOP.NP

type CollapseTo (POP :: (k -> *) -> [[k]] -> *) a = [[a]]
type AllN (POP :: (k -> *) -> [[k]] -> *) (c :: k -> Constraint) 
Instance details

Defined in Generics.SOP.NP

type AllN (POP :: (k -> *) -> [[k]] -> *) (c :: k -> Constraint) = All2 c

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 #

Variant of hcliftA3 that takes a constrained function.

Specification:

hcliftA3 p f xs ys zs = hcpure p (fn_3 f) ` hap ` xs ` hap ` ys ` hap ` zs

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 #

Variant of hcliftA2 that takes a constrained function.

Specification:

hcliftA2 p f xs ys = hcpure p (fn_2 f) ` hap ` xs ` hap ` ys

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 #

Variant of hliftA that takes a constrained function.

Specification:

hcliftA p f xs = hcpure p (fn f) ` hap ` 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:

hliftA3 f xs ys zs = hpure (fn_3 f) ` hap ` xs ` hap ` ys ` hap ` zs

Instances:

hliftA3, liftA3_NP  :: SListI  xs  => (forall a. f a -> f' a -> f'' a -> f''' a) -> NP  f xs  -> NP  f' xs  -> NP  f'' xs  -> NP  f''' xs
hliftA3, liftA3_NS  :: SListI  xs  => (forall a. f a -> f' a -> f'' a -> f''' a) -> NP  f xs  -> NP  f' xs  -> NS  f'' xs  -> NS  f''' xs
hliftA3, liftA3_POP :: SListI2 xss => (forall a. f a -> f' a -> f'' a -> f''' a) -> POP f xss -> POP f' xss -> POP f'' xss -> POP f''' xs
hliftA3, liftA3_SOP :: SListI2 xss => (forall a. f a -> f' a -> f'' a -> f''' a) -> POP f xss -> POP f' xss -> SOP f'' xss -> SOP 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 #

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:

hliftA2 f xs ys = hpure (fn_2 f) ` hap ` xs ` hap ` ys

Instances:

hliftA2, liftA2_NP  :: SListI  xs  => (forall a. f a -> f' a -> f'' a) -> NP  f xs  -> NP  f' xs  -> NP  f'' xs
hliftA2, liftA2_NS  :: SListI  xs  => (forall a. f a -> f' a -> f'' a) -> NP  f xs  -> NS  f' xs  -> NS  f'' xs
hliftA2, liftA2_POP :: SListI2 xss => (forall a. f a -> f' a -> f'' a) -> POP f xss -> POP f' xss -> POP f'' xss
hliftA2, liftA2_SOP :: SListI2 xss => (forall a. f a -> f' a -> f'' a) -> POP f xss -> SOP f' xss -> SOP f'' 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:

hliftA f xs = hpure (fn f) ` hap ` xs

Instances:

hliftA, liftA_NP  :: SListI  xs  => (forall a. f a -> f' a) -> NP  f xs  -> NP  f' xs
hliftA, liftA_NS  :: SListI  xs  => (forall a. f a -> f' a) -> NS  f xs  -> NS  f' xs
hliftA, liftA_POP :: SListI2 xss => (forall a. f a -> f' a) -> POP f xss -> POP f' xss
hliftA, liftA_SOP :: SListI2 xss => (forall a. f a -> f' a) -> SOP f xss -> SOP f' 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_2 :: (f a -> f' a -> f'' a) -> (f -.-> (f' -.-> f'')) a #

Construct a binary 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 #

A generalization of pure or return to higher kinds.

Minimal complete definition

hpure, hcpure

Methods

hpure :: SListIN h xs => (forall (a :: k). f a) -> h f xs #

Corresponds to pure directly.

Instances:

hpure, pure_NP  :: SListI  xs  => (forall a. f a) -> NP  f xs
hpure, pure_POP :: SListI2 xss => (forall a. f a) -> POP f 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 s where s :: 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 states.

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 xs is always satisfied. Therefore, we typically define hpure separately and directly, and make it a member of the class.

Instances:

hcpure, cpure_NP  :: (All  c xs ) => proxy c -> (forall a. c a => f a) -> NP  f xs
hcpure, cpure_POP :: (All2 c xss) => proxy c -> (forall a. c a => f a) -> POP f xss
Instances
HPure (POP :: (k -> *) -> [[k]] -> *) 
Instance details

Defined in Generics.SOP.NP

Methods

hpure :: SListIN POP xs => (forall (a :: k0). f a) -> POP f xs #

hcpure :: AllN POP c xs => proxy c -> (forall (a :: k0). c a => f a) -> POP f xs #

HPure (NP :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NP

Methods

hpure :: SListIN NP xs => (forall (a :: k0). f a) -> NP f xs #

hcpure :: AllN NP c xs => proxy c -> (forall (a :: k0). c a => f a) -> NP f xs #

newtype ((f :: k -> *) -.-> (g :: k -> *)) (a :: k) :: forall k. (k -> *) -> (k -> *) -> k -> * infixr 1 #

Lifted functions.

Constructors

Fn 

Fields

  • apFn :: f a -> g a
     

type family Prod (h :: (k -> *) -> l -> *) :: (k -> *) -> l -> * #

Maps a structure containing sums to the corresponding product structure.

Instances
type Prod (NS :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NS

type Prod (NS :: (k -> *) -> [k] -> *) = (NP :: (k -> *) -> [k] -> *)
type Prod (SOP :: (k -> *) -> [[k]] -> *) 
Instance details

Defined in Generics.SOP.NS

type Prod (SOP :: (k -> *) -> [[k]] -> *) = (POP :: (k -> *) -> [[k]] -> *)
type Prod (NP :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NP

type Prod (NP :: (k -> *) -> [k] -> *) = (NP :: (k -> *) -> [k] -> *)
type Prod (POP :: (k -> *) -> [[k]] -> *) 
Instance details

Defined in Generics.SOP.NP

type Prod (POP :: (k -> *) -> [[k]] -> *) = (POP :: (k -> *) -> [[k]] -> *)

class (Prod (Prod h) ~ Prod h, HPure (Prod h)) => HAp (h :: (k -> *) -> l -> *) where #

A generalization of <*>.

Minimal complete definition

hap

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  -> NP  f xs  -> NP  g xs
hap, ap_NS  :: NP  (f -.-> g) xs  -> NS  f xs  -> NS  g xs
hap, ap_POP :: POP (f -.-> g) xss -> POP f xss -> POP g xss
hap, ap_SOP :: POP (f -.-> g) xss -> SOP f xss -> SOP g xss
Instances
HAp (SOP :: (k -> *) -> [[k]] -> *) 
Instance details

Defined in Generics.SOP.NS

Methods

hap :: Prod SOP (f -.-> g) xs -> SOP f xs -> SOP g xs #

HAp (NS :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NS

Methods

hap :: Prod NS (f -.-> g) xs -> NS f xs -> NS g xs #

HAp (POP :: (k -> *) -> [[k]] -> *) 
Instance details

Defined in Generics.SOP.NP

Methods

hap :: Prod POP (f -.-> g) xs -> POP f xs -> POP g xs #

HAp (NP :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NP

Methods

hap :: Prod NP (f -.-> g) xs -> NP f xs -> NP g xs #

type family CollapseTo (h :: (k -> *) -> l -> *) x :: * #

Maps products to lists, and sums to identities.

Instances
type CollapseTo (NS :: (k -> *) -> [k] -> *) a 
Instance details

Defined in Generics.SOP.NS

type CollapseTo (NS :: (k -> *) -> [k] -> *) a = a
type CollapseTo (SOP :: (k -> *) -> [[k]] -> *) a 
Instance details

Defined in Generics.SOP.NS

type CollapseTo (SOP :: (k -> *) -> [[k]] -> *) a = [a]
type CollapseTo (NP :: (k -> *) -> [k] -> *) a 
Instance details

Defined in Generics.SOP.NP

type CollapseTo (NP :: (k -> *) -> [k] -> *) a = [a]
type CollapseTo (POP :: (k -> *) -> [[k]] -> *) a 
Instance details

Defined in Generics.SOP.NP

type CollapseTo (POP :: (k -> *) -> [[k]] -> *) a = [[a]]

class HCollapse (h :: (k -> *) -> l -> *) where #

A class for collapsing a heterogeneous structure into a homogeneous one.

Minimal complete definition

hcollapse

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) contains a single a, and an NP (K a) contains a list of as.

Instances:

hcollapse, collapse_NP  :: NP  (K a) xs  ->  [a]
hcollapse, collapse_NS  :: NS  (K a) xs  ->   a
hcollapse, collapse_POP :: POP (K a) xss -> [[a]]
hcollapse, collapse_SOP :: SOP (K a) xss ->  [a]
Instances
HCollapse (SOP :: (k -> *) -> [[k]] -> *) 
Instance details

Defined in Generics.SOP.NS

Methods

hcollapse :: SListIN SOP xs => SOP (K a) xs -> CollapseTo SOP a #

HCollapse (NS :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NS

Methods

hcollapse :: SListIN NS xs => NS (K a) xs -> CollapseTo NS a #

HCollapse (POP :: (k -> *) -> [[k]] -> *) 
Instance details

Defined in Generics.SOP.NP

Methods

hcollapse :: SListIN POP xs => POP (K a) xs -> CollapseTo POP a #

HCollapse (NP :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NP

Methods

hcollapse :: SListIN NP xs => NP (K a) xs -> CollapseTo NP a #

class HTraverse_ (h :: (k -> *) -> l -> *) where #

A generalization of traverse_ or foldMap.

Since: generics-sop-0.3.2.0

Minimal complete definition

hctraverse_, htraverse_

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  :: (All  c xs , Applicative g) => proxy c -> (forall a. c a => f a -> g ()) -> NP  f xs  -> g ()
hctraverse_, ctraverse__NS  :: (All2 c xs , Applicative g) => proxy c -> (forall a. c a => f a -> g ()) -> NS  f xs  -> g ()
hctraverse_, ctraverse__POP :: (All  c xss, Applicative g) => proxy c -> (forall a. c a => f a -> g ()) -> POP f xss -> g ()
hctraverse_, ctraverse__SOP :: (All2 c xss, Applicative g) => proxy c -> (forall a. c a => f a -> g ()) -> SOP f 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  :: (SListI  xs , 'Applicative g') => (forall a. f a -> g ()) -> NP  f xs  -> g ()
traverse_, traverse__NS  :: (SListI  xs , 'Applicative g') => (forall a. f a -> g ()) -> NS  f xs  -> g ()
traverse_, traverse__POP :: (SListI2 xss, 'Applicative g') => (forall a. f a -> g ()) -> POP f xss -> g ()
traverse_, traverse__SOP :: (SListI2 xss, 'Applicative g') => (forall a. f a -> g ()) -> SOP f xss -> g ()

Since: generics-sop-0.3.2.0

Instances
HTraverse_ (SOP :: (k -> *) -> [[k]] -> *) 
Instance details

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] -> *) 
Instance details

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]] -> *) 
Instance details

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] -> *) 
Instance details

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

hsequence', hctraverse', htraverse'

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  :: (SListI  xs , Applicative f) => NP  (f :.: g) xs  -> f (NP  g xs )
hsequence', sequence'_NS  :: (SListI  xs , Applicative f) => NS  (f :.: g) xs  -> f (NS  g xs )
hsequence', sequence'_POP :: (SListI2 xss, Applicative f) => POP (f :.: g) xss -> f (POP g xss)
hsequence', sequence'_SOP :: (SListI2 xss, Applicative f) => SOP (f :.: g) xss -> f (SOP g 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  :: (All  c xs , Applicative g) => proxy c -> (forall a. c a => f a -> g (f' a)) -> NP  f xs  -> g (NP  f' xs )
hctraverse', ctraverse'_NS  :: (All2 c xs , Applicative g) => proxy c -> (forall a. c a => f a -> g (f' a)) -> NS  f xs  -> g (NS  f' xs )
hctraverse', ctraverse'_POP :: (All  c xss, Applicative g) => proxy c -> (forall a. c a => f a -> g (f' a)) -> POP f xss -> g (POP f' xss)
hctraverse', ctraverse'_SOP :: (All2 c xss, Applicative g) => proxy c -> (forall a. c a => f a -> g (f' a)) -> SOP f xss -> g (SOP f' 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  :: (SListI  xs , Applicative g) => (forall a. c a => f a -> g (f' a)) -> NP  f xs  -> g (NP  f' xs )
htraverse', traverse'_NS  :: (SListI2 xs , Applicative g) => (forall a. c a => f a -> g (f' a)) -> NS  f xs  -> g (NS  f' xs )
htraverse', traverse'_POP :: (SListI  xss, Applicative g) => (forall a. c a => f a -> g (f' a)) -> POP f xss -> g (POP f' xss)
htraverse', traverse'_SOP :: (SListI2 xss, Applicative g) => (forall a. c a => f a -> g (f' a)) -> SOP f xss -> g (SOP f' xss)

Since: generics-sop-0.3.2.0

Instances
HSequence (SOP :: (k -> *) -> [[k]] -> *) 
Instance details

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] -> *) 
Instance details

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]] -> *) 
Instance details

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] -> *) 
Instance details

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

hindex

Methods

hindex :: h f xs -> Int #

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 x returns a number between 0 and n - 1 representing the index of the choice made by x.

Instances:

hindex, index_NS  :: NS  f xs -> Int
hindex, index_SOP :: SOP f 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

Instances
HIndex (SOP :: (k -> *) -> [[k]] -> *) 
Instance details

Defined in Generics.SOP.NS

Methods

hindex :: SOP f xs -> Int #

HIndex (NS :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NS

Methods

hindex :: NS f xs -> Int #

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

Instances
type UnProd (NP :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NS

type UnProd (NP :: (k -> *) -> [k] -> *) = (NS :: (k -> *) -> [k] -> *)
type UnProd (POP :: (k -> *) -> [[k]] -> *) 
Instance details

Defined in Generics.SOP.NS

type UnProd (POP :: (k -> *) -> [[k]] -> *) = (SOP :: (k -> *) -> [[k]] -> *)

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

hapInjs

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  :: SListI  xs  => NP  f xs -> [NS  f xs ]
hapInjs, apInjs_SOP :: SListI2 xss => POP f xs -> [SOP f 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

Instances
HApInjs (SOP :: (k -> *) -> [[k]] -> *) 
Instance details

Defined in Generics.SOP.NS

Methods

hapInjs :: SListIN SOP xs => Prod SOP f xs -> [SOP f xs] #

HApInjs (NS :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NS

Methods

hapInjs :: SListIN NS xs => Prod NS f xs -> [NS f xs] #

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

Minimal complete definition

hexpand, hcexpand

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  :: SListI xs  => (forall x . f x) -> NS  f xs  -> NP  f xs
hexpand, expand_SOP :: SListI2 xss => (forall x . f x) -> SOP f xss -> POP f 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  :: All  c xs  => proxy c -> (forall x . c x => f x) -> NS  f xs  -> NP  f xs
hcexpand, cexpand_SOP :: All2 c xss => proxy c -> (forall x . c x => f x) -> SOP f xss -> POP f 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

Instances
HExpand (SOP :: (k -> *) -> [[k]] -> *) 
Instance details

Defined in Generics.SOP.NS

Methods

hexpand :: SListIN (Prod SOP) xs => (forall (x :: k0). f x) -> SOP f xs -> Prod SOP f xs #

hcexpand :: AllN (Prod SOP) c xs => proxy c -> (forall (x :: k0). c x => f x) -> SOP f xs -> Prod SOP f xs #

HExpand (NS :: (k -> *) -> [k] -> *) 
Instance details

Defined in Generics.SOP.NS

Methods

hexpand :: SListIN (Prod NS) xs => (forall (x :: k0). f x) -> NS f xs -> Prod NS f xs #

hcexpand :: AllN (Prod NS) c xs => proxy c -> (forall (x :: k0). c x => f x) -> NS f xs -> Prod NS f xs #

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

Minimal complete definition

htrans, hcoerce

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

Instances
HTrans (SOP :: (k1 -> *) -> [[k1]] -> *) (SOP :: (k2 -> *) -> [[k2]] -> *) 
Instance details

Defined in Generics.SOP.NS

Methods

htrans :: AllZipN (Prod SOP) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> SOP f xs -> SOP g ys #

hcoerce :: (AllZipN (Prod SOP) (LiftedCoercible f g) xs ys, HTrans SOP SOP) => SOP f xs -> SOP g ys #

HTrans (NS :: (k1 -> *) -> [k1] -> *) (NS :: (k2 -> *) -> [k2] -> *) 
Instance details

Defined in Generics.SOP.NS

Methods

htrans :: AllZipN (Prod NS) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> NS f xs -> NS g ys #

hcoerce :: (AllZipN (Prod NS) (LiftedCoercible f g) xs ys, HTrans NS NS) => NS f xs -> NS g ys #

HTrans (POP :: (k1 -> *) -> [[k1]] -> *) (POP :: (k2 -> *) -> [[k2]] -> *) 
Instance details

Defined in Generics.SOP.NP

Methods

htrans :: AllZipN (Prod POP) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> POP f xs -> POP g ys #

hcoerce :: (AllZipN (Prod POP) (LiftedCoercible f g) xs ys, HTrans POP POP) => POP f xs -> POP g ys #

HTrans (NP :: (k1 -> *) -> [k1] -> *) (NP :: (k2 -> *) -> [k2] -> *) 
Instance details

Defined in Generics.SOP.NP

Methods

htrans :: AllZipN (Prod NP) c xs ys => proxy c -> (forall (x :: k10) (y :: k20). c x y => f x -> g y) -> NP f xs -> NP g ys #

hcoerce :: (AllZipN (Prod NP) (LiftedCoercible f g) xs ys, HTrans NP NP) => NP f xs -> NP g ys #

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]) 
Instance details

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]]) 
Instance details

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]) 
Instance details

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) 
Instance details

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]]) 
Instance details

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 :. g, the kind of f is k -> Constraint. The kind of g, 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 xs satisfy Show, 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) 
Instance details

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) 
Instance details

Defined in Generics.SOP.Constraint

class Top (x :: k) #

A constraint that can always be satisfied.

Since: generics-sop-0.2

Instances
Top (x :: k) 
Instance details

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) 
Instance details

Defined in Generics.SOP.NS

type AllN (NS :: (k -> *) -> [k] -> *) (c :: k -> Constraint) = All c
type AllN (SOP :: (k -> *) -> [[k]] -> *) (c :: k -> Constraint) 
Instance details

Defined in Generics.SOP.NS

type AllN (SOP :: (k -> *) -> [[k]] -> *) (c :: k -> Constraint) = All2 c
type AllN (NP :: (k -> *) -> [k] -> *) (c :: k -> Constraint) 
Instance details

Defined in Generics.SOP.NP

type AllN (NP :: (k -> *) -> [k] -> *) (c :: k -> Constraint) = All c
type AllN (POP :: (k -> *) -> [[k]] -> *) (c :: k -> Constraint) 
Instance details

Defined in Generics.SOP.NP

type AllN (POP :: (k -> *) -> [[k]] -> *) (c :: k -> Constraint) = All2 c

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) 
Instance details

Defined in Generics.SOP.NP

type AllZipN (NP :: (k -> *) -> [k] -> *) (c :: a -> b -> Constraint) = AllZip c
type AllZipN (POP :: (k -> *) -> [[k]] -> *) (c :: a -> b -> Constraint) 
Instance details

Defined in Generics.SOP.NP

type AllZipN (POP :: (k -> *) -> [[k]] -> *) (c :: a -> b -> Constraint) = AllZip2 c

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

shape :: SListI xs => Shape xs #

The shape of a type-level list.

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

Constructors

SNil :: SList ([] :: [k]) 
SCons :: SList (x ': xs) 
Instances
Eq (SList xs) 
Instance details

Defined in Generics.SOP.Sing

Methods

(==) :: SList xs -> SList xs -> Bool #

(/=) :: SList xs -> SList xs -> Bool #

Ord (SList xs) 
Instance details

Defined in Generics.SOP.Sing

Methods

compare :: SList xs -> SList xs -> Ordering #

(<) :: SList xs -> SList xs -> Bool #

(<=) :: SList xs -> SList xs -> Bool #

(>) :: SList xs -> SList xs -> Bool #

(>=) :: SList xs -> SList xs -> Bool #

max :: SList xs -> SList xs -> SList xs #

min :: SList xs -> SList xs -> SList xs #

Show (SList xs) 
Instance details

Defined in Generics.SOP.Sing

Methods

showsPrec :: Int -> SList xs -> ShowS #

show :: SList xs -> String #

showList :: [SList xs] -> ShowS #

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

sList

Methods

sList :: SList xs #

Get hold of the explicit singleton (that one can then pattern match on).

Instances
SListI ([] :: [k]) 
Instance details

Defined in Generics.SOP.Sing

Methods

sList :: SList [] #

SListI xs => SListI (x ': xs :: [k]) 
Instance details

Defined in Generics.SOP.Sing

Methods

sList :: SList (x ': xs) #

class SListI xs => SingI (xs :: [k]) where #

General class for implicit singletons.

Just provided for limited backward compatibility.

Minimal complete definition

sing

Methods

sing :: Sing xs #

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)

Constructors

ShapeNil :: Shape ([] :: [k]) 
ShapeCons :: Shape (x ': xs) 
Instances
Eq (Shape xs) 
Instance details

Defined in Generics.SOP.Sing

Methods

(==) :: Shape xs -> Shape xs -> Bool #

(/=) :: Shape xs -> Shape xs -> Bool #

Ord (Shape xs) 
Instance details

Defined in Generics.SOP.Sing

Methods

compare :: Shape xs -> Shape xs -> Ordering #

(<) :: Shape xs -> Shape xs -> Bool #

(<=) :: Shape xs -> Shape xs -> Bool #

(>) :: Shape xs -> Shape xs -> Bool #

(>=) :: Shape xs -> Shape xs -> Bool #

max :: Shape xs -> Shape xs -> Shape xs #

min :: Shape xs -> Shape xs -> Shape xs #

Show (Shape xs) 
Instance details

Defined in Generics.SOP.Sing

Methods

showsPrec :: Int -> Shape xs -> ShowS #

show :: Shape xs -> String #

showList :: [Shape xs] -> ShowS #

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

mapKII :: (a -> b -> c) -> K a d -> I b -> I c #

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

mapIKI :: (a -> b -> c) -> I a -> K b d -> I c #

Lift the given function.

Since: generics-sop-0.2.5.0

mapIIK :: (a -> b -> c) -> I a -> I b -> K c d #

Lift the given function.

Since: generics-sop-0.2.5.0

mapIII :: (a -> b -> c) -> I a -> I b -> I c #

Lift the given function.

Since: generics-sop-0.2.5.0

mapKK :: (a -> b) -> K a c -> K b d #

Lift the given function.

Since: generics-sop-0.2.5.0

mapKI :: (a -> b) -> K a c -> I b #

Lift the given function.

Since: generics-sop-0.2.5.0

mapIK :: (a -> b) -> I a -> K b c #

Lift the given function.

Since: generics-sop-0.2.5.0

mapII :: (a -> b) -> I a -> I b #

Lift the given function.

Since: generics-sop-0.2.5.0

unComp :: (f :.: g) p -> f (g p) #

Extract the contents of a Comp value.

unI :: I a -> a #

Extract the contents of an I value.

unK :: K a b -> a #

Extract the contents of a K value.

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

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

liftEq2 :: (a -> b -> Bool) -> (c -> d -> Bool) -> K a c -> K b d -> Bool #

Ord2 (K :: * -> * -> *)

Since: generics-sop-0.2.4.0

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

liftCompare2 :: (a -> b -> Ordering) -> (c -> d -> Ordering) -> K a c -> K b d -> Ordering #

Read2 (K :: * -> * -> *)

Since: generics-sop-0.2.4.0

Instance details

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

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

liftShowsPrec2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> Int -> K a b -> ShowS #

liftShowList2 :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> (Int -> b -> ShowS) -> ([b] -> ShowS) -> [K a b] -> ShowS #

NFData2 (K :: * -> * -> *)

Since: generics-sop-0.2.5.0

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

liftRnf2 :: (a -> ()) -> (b -> ()) -> K a b -> () #

Functor (K a :: * -> *) 
Instance details

Defined in Generics.SOP.BasicFunctors

Methods

fmap :: (a0 -> b) -> K a a0 -> K a b #

(<$) :: a0 -> K a b -> K a a0 #

Monoid a => Applicative (K a :: * -> *) 
Instance details

Defined in Generics.SOP.BasicFunctors

Methods

pure :: a0 -> K a a0 #

(<*>) :: K a (a0 -> b) -> K a a0 -> K a b #

liftA2 :: (a0 -> b -> c) -> K a a0 -> K a b -> K a c #

(*>) :: K a a0 -> K a b -> K a b #

(<*) :: K a a0 -> K a b -> K a a0 #

Foldable (K a :: * -> *) 
Instance details

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 #

toList :: K a a0 -> [a0] #

null :: K a a0 -> Bool #

length :: K a a0 -> Int #

elem :: Eq a0 => a0 -> K a a0 -> Bool #

maximum :: Ord a0 => K a a0 -> a0 #

minimum :: Ord a0 => K a a0 -> a0 #

sum :: Num a0 => K a a0 -> a0 #

product :: Num a0 => K a a0 -> a0 #

Traversable (K a :: * -> *) 
Instance details

Defined in Generics.SOP.BasicFunctors

Methods

traverse :: Applicative f => (a0 -> f b) -> K a a0 -> f (K a b) #

sequenceA :: Applicative f => K a (f a0) -> f (K a a0) #

mapM :: Monad m => (a0 -> m b) -> K a a0 -> m (K a b) #

sequence :: Monad m => K a (m a0) -> m (K a a0) #

Eq a => Eq1 (K a :: * -> *)

Since: generics-sop-0.2.4.0

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

liftEq :: (a0 -> b -> Bool) -> K a a0 -> K a b -> Bool #

Ord a => Ord1 (K a :: * -> *)

Since: generics-sop-0.2.4.0

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

liftCompare :: (a0 -> b -> Ordering) -> K a a0 -> K a b -> Ordering #

Read a => Read1 (K a :: * -> *)

Since: generics-sop-0.2.4.0

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

liftReadsPrec :: (Int -> ReadS a0) -> ReadS [a0] -> Int -> ReadS (K a a0) #

liftReadList :: (Int -> ReadS a0) -> ReadS [a0] -> ReadS [K a a0] #

liftReadPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec (K a a0) #

liftReadListPrec :: ReadPrec a0 -> ReadPrec [a0] -> ReadPrec [K a a0] #

Show a => Show1 (K a :: * -> *)

Since: generics-sop-0.2.4.0

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

liftShowsPrec :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> Int -> K a a0 -> ShowS #

liftShowList :: (Int -> a0 -> ShowS) -> ([a0] -> ShowS) -> [K a a0] -> ShowS #

NFData a => NFData1 (K a :: * -> *)

Since: generics-sop-0.2.5.0

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

liftRnf :: (a0 -> ()) -> K a a0 -> () #

Eq a => Eq (K a b) 
Instance details

Defined in Generics.SOP.BasicFunctors

Methods

(==) :: K a b -> K a b -> Bool #

(/=) :: K a b -> K a b -> Bool #

Ord a => Ord (K a b) 
Instance details

Defined in Generics.SOP.BasicFunctors

Methods

compare :: K a b -> K a b -> Ordering #

(<) :: K a b -> K a b -> Bool #

(<=) :: K a b -> K a b -> Bool #

(>) :: K a b -> K a b -> Bool #

(>=) :: K a b -> K a b -> Bool #

max :: K a b -> K a b -> K a b #

min :: K a b -> K a b -> K a b #

Read a => Read (K a b) 
Instance details

Defined in Generics.SOP.BasicFunctors

Methods

readsPrec :: Int -> ReadS (K a b) #

readList :: ReadS [K a b] #

readPrec :: ReadPrec (K a b) #

readListPrec :: ReadPrec [K a b] #

Show a => Show (K a b) 
Instance details

Defined in Generics.SOP.BasicFunctors

Methods

showsPrec :: Int -> K a b -> ShowS #

show :: K a b -> String #

showList :: [K a b] -> ShowS #

Generic (K a b) 
Instance details

Defined in Generics.SOP.BasicFunctors

Associated Types

type Rep (K a b) :: * -> * #

Methods

from :: K a b -> Rep (K a b) x #

to :: Rep (K a b) x -> K a b #

NFData a => NFData (K a b)

Since: generics-sop-0.2.5.0

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

rnf :: K a b -> () #

type Rep (K a b) 
Instance details

Defined in Generics.SOP.BasicFunctors

type Rep (K a b) = D1 (MetaData "K" "Generics.SOP.BasicFunctors" "generics-sop-0.3.2.0-5JX38dNigUk7e65oSELmom" True) (C1 (MetaCons "K" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Code (K a b) 
Instance details

Defined in Generics.SOP.Instances

type Code (K a b) = (a ': ([] :: [*])) ': ([] :: [[*]])
type DatatypeInfoOf (K a b) 
Instance details

Defined in Generics.SOP.Instances

type DatatypeInfoOf (K a b) = Newtype "Generics.SOP.BasicFunctors" "K" (Constructor "K")

newtype I a #

The identity type functor.

Like Identity, but with a shorter name.

Constructors

I a 
Instances
Monad I 
Instance details

Defined in Generics.SOP.BasicFunctors

Methods

(>>=) :: I a -> (a -> I b) -> I b #

(>>) :: I a -> I b -> I b #

return :: a -> I a #

fail :: String -> I a #

Functor I 
Instance details

Defined in Generics.SOP.BasicFunctors

Methods

fmap :: (a -> b) -> I a -> I b #

(<$) :: a -> I b -> I a #

Applicative I 
Instance details

Defined in Generics.SOP.BasicFunctors

Methods

pure :: a -> I a #

(<*>) :: I (a -> b) -> I a -> I b #

liftA2 :: (a -> b -> c) -> I a -> I b -> I c #

(*>) :: I a -> I b -> I b #

(<*) :: I a -> I b -> I a #

Foldable I 
Instance details

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 #

toList :: I a -> [a] #

null :: I a -> Bool #

length :: I a -> Int #

elem :: Eq a => a -> I a -> Bool #

maximum :: Ord a => I a -> a #

minimum :: Ord a => I a -> a #

sum :: Num a => I a -> a #

product :: Num a => I a -> a #

Traversable I 
Instance details

Defined in Generics.SOP.BasicFunctors

Methods

traverse :: Applicative f => (a -> f b) -> I a -> f (I b) #

sequenceA :: Applicative f => I (f a) -> f (I a) #

mapM :: Monad m => (a -> m b) -> I a -> m (I b) #

sequence :: Monad m => I (m a) -> m (I a) #

Eq1 I

Since: generics-sop-0.2.4.0

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

liftEq :: (a -> b -> Bool) -> I a -> I b -> Bool #

Ord1 I

Since: generics-sop-0.2.4.0

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

liftCompare :: (a -> b -> Ordering) -> I a -> I b -> Ordering #

Read1 I

Since: generics-sop-0.2.4.0

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS (I a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [I a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec (I a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [I a] #

Show1 I

Since: generics-sop-0.2.4.0

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> I a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [I a] -> ShowS #

NFData1 I

Since: generics-sop-0.2.5.0

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

liftRnf :: (a -> ()) -> I a -> () #

Eq a => Eq (I a) 
Instance details

Defined in Generics.SOP.BasicFunctors

Methods

(==) :: I a -> I a -> Bool #

(/=) :: I a -> I a -> Bool #

Ord a => Ord (I a) 
Instance details

Defined in Generics.SOP.BasicFunctors

Methods

compare :: I a -> I a -> Ordering #

(<) :: I a -> I a -> Bool #

(<=) :: I a -> I a -> Bool #

(>) :: I a -> I a -> Bool #

(>=) :: I a -> I a -> Bool #

max :: I a -> I a -> I a #

min :: I a -> I a -> I a #

Read a => Read (I a) 
Instance details

Defined in Generics.SOP.BasicFunctors

Methods

readsPrec :: Int -> ReadS (I a) #

readList :: ReadS [I a] #

readPrec :: ReadPrec (I a) #

readListPrec :: ReadPrec [I a] #

Show a => Show (I a) 
Instance details

Defined in Generics.SOP.BasicFunctors

Methods

showsPrec :: Int -> I a -> ShowS #

show :: I a -> String #

showList :: [I a] -> ShowS #

Generic (I a) 
Instance details

Defined in Generics.SOP.BasicFunctors

Associated Types

type Rep (I a) :: * -> * #

Methods

from :: I a -> Rep (I a) x #

to :: Rep (I a) x -> I a #

NFData a => NFData (I a)

Since: generics-sop-0.2.5.0

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

rnf :: I a -> () #

type Rep (I a) 
Instance details

Defined in Generics.SOP.BasicFunctors

type Rep (I a) = D1 (MetaData "I" "Generics.SOP.BasicFunctors" "generics-sop-0.3.2.0-5JX38dNigUk7e65oSELmom" True) (C1 (MetaCons "I" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a)))
type Code (I a) 
Instance details

Defined in Generics.SOP.Instances

type Code (I a) = (a ': ([] :: [*])) ': ([] :: [[*]])
type DatatypeInfoOf (I a) 
Instance details

Defined in Generics.SOP.Instances

type DatatypeInfoOf (I a) = Newtype "Generics.SOP.BasicFunctors" "I" (Constructor "I")

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) 
Instance details

Defined in Generics.SOP.BasicFunctors

Methods

fmap :: (a -> b) -> (f :.: g) a -> (f :.: g) b #

(<$) :: a -> (f :.: g) b -> (f :.: g) a #

(Applicative f, Applicative g) => Applicative (f :.: g)

Since: generics-sop-0.2.5.0

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

pure :: a -> (f :.: g) a #

(<*>) :: (f :.: g) (a -> b) -> (f :.: g) a -> (f :.: g) b #

liftA2 :: (a -> b -> c) -> (f :.: g) a -> (f :.: g) b -> (f :.: g) c #

(*>) :: (f :.: g) a -> (f :.: g) b -> (f :.: g) b #

(<*) :: (f :.: g) a -> (f :.: g) b -> (f :.: g) a #

(Foldable f, Foldable g) => Foldable (f :.: g)

Since: generics-sop-0.2.5.0

Instance details

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] #

null :: (f :.: g) a -> Bool #

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 #

sum :: Num a => (f :.: g) a -> a #

product :: Num a => (f :.: g) a -> a #

(Traversable f, Traversable g) => Traversable (f :.: g)

Since: generics-sop-0.2.5.0

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

traverse :: Applicative f0 => (a -> f0 b) -> (f :.: g) a -> f0 ((f :.: g) b) #

sequenceA :: Applicative f0 => (f :.: g) (f0 a) -> f0 ((f :.: g) a) #

mapM :: Monad m => (a -> m b) -> (f :.: g) a -> m ((f :.: g) b) #

sequence :: Monad m => (f :.: g) (m a) -> m ((f :.: g) a) #

(Eq1 f, Eq1 g) => Eq1 (f :.: g)

Since: generics-sop-0.2.4.0

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

liftEq :: (a -> b -> Bool) -> (f :.: g) a -> (f :.: g) b -> Bool #

(Ord1 f, Ord1 g) => Ord1 (f :.: g)

Since: generics-sop-0.2.4.0

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

liftCompare :: (a -> b -> Ordering) -> (f :.: g) a -> (f :.: g) b -> Ordering #

(Read1 f, Read1 g) => Read1 (f :.: g)

Since: generics-sop-0.2.4.0

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

liftReadsPrec :: (Int -> ReadS a) -> ReadS [a] -> Int -> ReadS ((f :.: g) a) #

liftReadList :: (Int -> ReadS a) -> ReadS [a] -> ReadS [(f :.: g) a] #

liftReadPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec ((f :.: g) a) #

liftReadListPrec :: ReadPrec a -> ReadPrec [a] -> ReadPrec [(f :.: g) a] #

(Show1 f, Show1 g) => Show1 (f :.: g)

Since: generics-sop-0.2.4.0

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

liftShowsPrec :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> Int -> (f :.: g) a -> ShowS #

liftShowList :: (Int -> a -> ShowS) -> ([a] -> ShowS) -> [(f :.: g) a] -> ShowS #

(NFData1 f, NFData1 g) => NFData1 (f :.: g)

Since: generics-sop-0.2.5.0

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

liftRnf :: (a -> ()) -> (f :.: g) a -> () #

(Eq1 f, Eq1 g, Eq a) => Eq ((f :.: g) a) 
Instance details

Defined in Generics.SOP.BasicFunctors

Methods

(==) :: (f :.: g) a -> (f :.: g) a -> Bool #

(/=) :: (f :.: g) a -> (f :.: g) a -> Bool #

(Ord1 f, Ord1 g, Ord a) => Ord ((f :.: g) a) 
Instance details

Defined in Generics.SOP.BasicFunctors

Methods

compare :: (f :.: g) a -> (f :.: g) a -> Ordering #

(<) :: (f :.: g) a -> (f :.: g) a -> Bool #

(<=) :: (f :.: g) a -> (f :.: g) a -> Bool #

(>) :: (f :.: g) a -> (f :.: g) a -> Bool #

(>=) :: (f :.: g) a -> (f :.: g) a -> Bool #

max :: (f :.: g) a -> (f :.: g) a -> (f :.: g) a #

min :: (f :.: g) a -> (f :.: g) a -> (f :.: g) a #

(Read1 f, Read1 g, Read a) => Read ((f :.: g) a) 
Instance details

Defined in Generics.SOP.BasicFunctors

Methods

readsPrec :: Int -> ReadS ((f :.: g) a) #

readList :: ReadS [(f :.: g) a] #

readPrec :: ReadPrec ((f :.: g) a) #

readListPrec :: ReadPrec [(f :.: g) a] #

(Show1 f, Show1 g, Show a) => Show ((f :.: g) a) 
Instance details

Defined in Generics.SOP.BasicFunctors

Methods

showsPrec :: Int -> (f :.: g) a -> ShowS #

show :: (f :.: g) a -> String #

showList :: [(f :.: g) a] -> ShowS #

Generic ((f :.: g) p) 
Instance details

Defined in Generics.SOP.BasicFunctors

Associated Types

type Rep ((f :.: g) p) :: * -> * #

Methods

from :: (f :.: g) p -> Rep ((f :.: g) p) x #

to :: Rep ((f :.: g) p) x -> (f :.: g) p #

NFData (f (g a)) => NFData ((f :.: g) a)

Since: generics-sop-0.2.5.0

Instance details

Defined in Generics.SOP.BasicFunctors

Methods

rnf :: (f :.: g) a -> () #

type Rep ((f :.: g) p) 
Instance details

Defined in Generics.SOP.BasicFunctors

type Rep ((f :.: g) p) = D1 (MetaData ":.:" "Generics.SOP.BasicFunctors" "generics-sop-0.3.2.0-5JX38dNigUk7e65oSELmom" True) (C1 (MetaCons "Comp" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (f (g p)))))
type Code ((f :.: g) p) 
Instance details

Defined in Generics.SOP.Instances

type Code ((f :.: g) p) = (f (g p) ': ([] :: [*])) ': ([] :: [[*]])
type DatatypeInfoOf ((f :.: g) p) 
Instance details

Defined in Generics.SOP.Instances

type DatatypeInfoOf ((f :.: g) p) = Newtype "Generics.SOP.BasicFunctors" ":.:" (Constructor "Comp")

deriveGeneric :: Name -> Q [Dec] #

Generate generics-sop boilerplate for the given datatype.

This function takes the name of a datatype and generates:

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

Example: If you have the datatype

data Tree = Leaf Int | Node Tree Tree

and say

deriveGeneric ''Tree

then you get code that is equivalent to:

instance Generic Tree where

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

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

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

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

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

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