schemas-0.3.0.2: schema guided serialization

Safe HaskellNone
LanguageHaskell2010

Schemas

Contents

Description

As a simple example of a schema, let's consider a simple record type:

 import Schemas
 import Schemas.SOP

 data Person = Person
   { name      :: String
   , age       :: Int
   , addresses :: [String]
   }

 personSchema :: TypedSchema Person
 personSchema = record $ Person
   <$> fieldWith string "name" name
   <*> fieldWith int    "age"  age
   <*> fieldWith (list string) "addresses" addresses

Or, by relying on the HasSchema type class:

 personSchema :: TypedSchema Person
 personSchema = record $ Person
   <$> field "name" name
   <*> field "age"  age
   <*> field "addresses" addresses

Or, if the type is SOP generic:

personSchema = gSchema defOptions
Synopsis

Typed schemas

data TypedSchemaFlex from a Source #

TypedSchemaFlex enc dec is a schema for encoding from enc and decoding to dec. Usually we want enc and dec to be the same type but this flexibility comes in handy for composition.

Instances
Profunctor TypedSchemaFlex Source # 
Instance details

Defined in Schemas.Internal

Methods

dimap :: (a -> b) -> (c -> d) -> TypedSchemaFlex b c -> TypedSchemaFlex a d #

lmap :: (a -> b) -> TypedSchemaFlex b c -> TypedSchemaFlex a c #

rmap :: (b -> c) -> TypedSchemaFlex a b -> TypedSchemaFlex a c #

(#.) :: Coercible c b => q b c -> TypedSchemaFlex a b -> TypedSchemaFlex a c #

(.#) :: Coercible b a => TypedSchemaFlex b c -> q a b -> TypedSchemaFlex a c #

Functor (TypedSchemaFlex from) Source # 
Instance details

Defined in Schemas.Internal

Methods

fmap :: (a -> b) -> TypedSchemaFlex from a -> TypedSchemaFlex from b #

(<$) :: a -> TypedSchemaFlex from b -> TypedSchemaFlex from a #

Show (TypedSchemaFlex from a) Source # 
Instance details

Defined in Schemas.Internal

Methods

showsPrec :: Int -> TypedSchemaFlex from a -> ShowS #

show :: TypedSchemaFlex from a -> String #

showList :: [TypedSchemaFlex from a] -> ShowS #

Semigroup (TypedSchemaFlex f a) Source # 
Instance details

Defined in Schemas.Internal

Monoid a => Monoid (TypedSchemaFlex f a) Source # 
Instance details

Defined in Schemas.Internal

class HasSchema a where Source #

Instances
HasSchema Bool Source # 
Instance details

Defined in Schemas.Class

HasSchema Double Source # 
Instance details

Defined in Schemas.Class

HasSchema Int Source # 
Instance details

Defined in Schemas.Class

HasSchema Integer Source # 
Instance details

Defined in Schemas.Class

HasSchema Natural Source # 
Instance details

Defined in Schemas.Class

HasSchema () Source # 
Instance details

Defined in Schemas.Class

Methods

schema :: TypedSchema () Source #

HasSchema Scientific Source # 
Instance details

Defined in Schemas.Class

HasSchema Text Source # 
Instance details

Defined in Schemas.Class

HasSchema Value Source # 
Instance details

Defined in Schemas.Class

HasSchema String Source # 
Instance details

Defined in Schemas.Class

HasSchema Field Source # 
Instance details

Defined in Schemas.Class

HasSchema Schema Source # 
Instance details

Defined in Schemas.Class

HasSchema SchemaName Source # 
Instance details

Defined in Schemas.Class

HasSchema OpenApi2Type Source # 
Instance details

Defined in Schemas.OpenApi2

HasSchema OpenApi2Schema Source # 
Instance details

Defined in Schemas.OpenApi2

HasSchema OpenApi2Document Source # 
Instance details

Defined in Schemas.OpenApi2

HasSchema a => HasSchema [a] Source # 
Instance details

Defined in Schemas.Class

Methods

schema :: TypedSchema [a] Source #

HasSchema a => HasSchema (Identity a) Source # 
Instance details

Defined in Schemas.Class

HasSchema a => HasSchema (NonEmpty a) Source # 
Instance details

Defined in Schemas.Class

(Eq a, Hashable a, HasSchema a) => HasSchema (HashSet a) Source # 
Instance details

Defined in Schemas.Class

HasSchema a => HasSchema (Vector a) Source # 
Instance details

Defined in Schemas.Class

(HasSchema a, HasSchema b) => HasSchema (Either a b) Source # 
Instance details

Defined in Schemas.Class

Methods

schema :: TypedSchema (Either a b) Source #

(HasSchema a, HasSchema b) => HasSchema (a, b) Source # 
Instance details

Defined in Schemas.Class

Methods

schema :: TypedSchema (a, b) Source #

(Eq key, Hashable key, HasSchema a, Key key) => HasSchema (HashMap key a) Source # 
Instance details

Defined in Schemas.Class

Methods

schema :: TypedSchema (HashMap key a) Source #

(HasSchema a, HasSchema b, HasSchema c) => HasSchema (a, b, c) Source # 
Instance details

Defined in Schemas.Class

Methods

schema :: TypedSchema (a, b, c) Source #

(HasSchema a, HasSchema b, HasSchema c, HasSchema d) => HasSchema (a, b, c, d) Source # 
Instance details

Defined in Schemas.Class

Methods

schema :: TypedSchema (a, b, c, d) Source #

(HasSchema a, HasSchema b, HasSchema c, HasSchema d, HasSchema e) => HasSchema (a, b, c, d, e) Source # 
Instance details

Defined in Schemas.Class

Methods

schema :: TypedSchema (a, b, c, d, e) Source #

Construction

enum :: Eq a => (a -> Text) -> NonEmpty a -> TypedSchema a Source #

enum values mapping construct a schema for a non empty set of values with a Text mapping

readShow :: (Read a, Show a) => TypedSchema a Source #

A schema for types that can be parsed and pretty-printed. The resulting schema is opaque and cannot be subtyped/versioned, so this constructor is best used for primitive value

list :: IsList l => TypedSchema (Item l) -> TypedSchema l Source #

list sc is the schema for a list of values with schema sc

string :: TypedSchema String Source #

The schema of String values

vector :: TypedSchema a -> TypedSchema (Vector a) Source #

vector sc is the schema for a vector of values with schema sc

class Key a where Source #

Methods

fromKey :: Text -> a Source #

toKey :: a -> Text Source #

Instances
Key Text Source # 
Instance details

Defined in Schemas.Class

Key String Source # 
Instance details

Defined in Schemas.Class

stringMap :: TypedSchema a -> TypedSchema (HashMap Text a) Source #

stringMap sc is the schema for a stringmap where the values have schema sc

viaJSON :: (FromJSON a, ToJSON a) => Text -> TypedSchema a Source #

viaJson label constructs a schema reusing existing aeson instances. The resulting schema is opaque and cannot be subtyped and/or versioned, so this constructor should be used sparingly. The label is used to describe the extracted Schema.

viaIso :: Iso' a b -> TypedSchema a -> TypedSchema b Source #

Apply an isomorphism to a schema

Applicative record definition

record :: RecordFields from a -> TypedSchemaFlex from a Source #

Wrap an applicative record schema

data RecordFields from a Source #

An Alternative profunctor for defining record schemas with versioning

 schemaPerson = Person
            <$> (field "name" name <|> field "full name" name)
            <*> (field "age" age <|> pure -1)
Instances
Profunctor RecordFields Source # 
Instance details

Defined in Schemas.Internal

Methods

dimap :: (a -> b) -> (c -> d) -> RecordFields b c -> RecordFields a d #

lmap :: (a -> b) -> RecordFields b c -> RecordFields a c #

rmap :: (b -> c) -> RecordFields a b -> RecordFields a c #

(#.) :: Coercible c b => q b c -> RecordFields a b -> RecordFields a c #

(.#) :: Coercible b a => RecordFields b c -> q a b -> RecordFields a c #

Functor (RecordFields from) Source # 
Instance details

Defined in Schemas.Internal

Methods

fmap :: (a -> b) -> RecordFields from a -> RecordFields from b #

(<$) :: a -> RecordFields from b -> RecordFields from a #

Applicative (RecordFields from) Source # 
Instance details

Defined in Schemas.Internal

Methods

pure :: a -> RecordFields from a #

(<*>) :: RecordFields from (a -> b) -> RecordFields from a -> RecordFields from b #

liftA2 :: (a -> b -> c) -> RecordFields from a -> RecordFields from b -> RecordFields from c #

(*>) :: RecordFields from a -> RecordFields from b -> RecordFields from b #

(<*) :: RecordFields from a -> RecordFields from b -> RecordFields from a #

Alternative (RecordFields from) Source # 
Instance details

Defined in Schemas.Internal

Methods

empty :: RecordFields from a #

(<|>) :: RecordFields from a -> RecordFields from a -> RecordFields from a #

some :: RecordFields from a -> RecordFields from [a] #

many :: RecordFields from a -> RecordFields from [a] #

Semigroup (RecordFields from a) Source # 
Instance details

Defined in Schemas.Internal

Methods

(<>) :: RecordFields from a -> RecordFields from a -> RecordFields from a #

sconcat :: NonEmpty (RecordFields from a) -> RecordFields from a #

stimes :: Integral b => b -> RecordFields from a -> RecordFields from a #

Monoid (RecordFields from a) Source # 
Instance details

Defined in Schemas.Internal

Methods

mempty :: RecordFields from a #

mappend :: RecordFields from a -> RecordFields from a -> RecordFields from a #

mconcat :: [RecordFields from a] -> RecordFields from a #

data RecordField from a Source #

Instances
Profunctor RecordField Source # 
Instance details

Defined in Schemas.Internal

Methods

dimap :: (a -> b) -> (c -> d) -> RecordField b c -> RecordField a d #

lmap :: (a -> b) -> RecordField b c -> RecordField a c #

rmap :: (b -> c) -> RecordField a b -> RecordField a c #

(#.) :: Coercible c b => q b c -> RecordField a b -> RecordField a c #

(.#) :: Coercible b a => RecordField b c -> q a b -> RecordField a c #

field :: HasSchema a => Text -> (from -> a) -> RecordFields from a Source #

field name get introduces a field with the default schema for the type

fieldWith :: TypedSchema a -> Text -> (from -> a) -> RecordFields from a Source #

fieldWith sc n get introduces a field

fieldWith' :: TypedSchemaFlex from a -> Text -> RecordFields from a Source #

Generalised version of fieldWith

optField :: forall a from. HasSchema a => Text -> (from -> Maybe a) -> RecordFields from (Maybe a) Source #

optField name get introduces an optional field with the default schema for the type

optFieldWith :: forall a from. TypedSchemaFlex from (Maybe a) -> Text -> RecordFields from (Maybe a) Source #

A generalized version of optField. Does not handle infinite/circular data.

optFieldEither :: forall a from e. HasSchema a => Text -> (from -> Either e a) -> e -> RecordFields from (Either e a) Source #

optFieldEither name get introduces an optional field with the default schema for the type

optFieldEitherWith :: TypedSchemaFlex from (Either e a) -> Text -> e -> RecordFields from (Either e a) Source #

A generalized version of optFieldEither. Does not handle infinite/circular data

optFieldGeneral :: forall a from. TypedSchemaFlex from a -> Text -> a -> RecordFields from a Source #

The most general introduction form for optional alts

fieldName :: RecordField from a -> Text Source #

Name of the field

fieldNameL :: Lens' (RecordField from a) Text Source #

Lens for the fieldName attribute

overFieldNames :: (Text -> Text) -> RecordFields from a -> RecordFields from a Source #

Map a function over all the field names

extractFields :: RecordFields from to -> [[(Text, Field)]] Source #

Extract all the field groups (from alternatives) in the record

Partial schemas

liftJust :: TypedSchemaFlex a b -> TypedSchemaFlex (Maybe a) (Maybe b) Source #

liftJust = liftPrism _Just

liftRight :: TypedSchemaFlex a b -> TypedSchemaFlex (Either c a) (Either c b) Source #

liftRight = liftPrism _Right

liftPrism :: Text -> Prism s t a b -> TypedSchemaFlex a b -> TypedSchemaFlex s t Source #

Project a schema through a Prism. Returns a partial schema. When encoding/decoding a value that doesn't fit the prism, an optional field will be omitted, and a required field will cause this alternative to be aborted.

Unions

union :: NonEmpty (Text, TypedSchema a) -> TypedSchema a Source #

The schema of discriminated unions

  import Schemas
  import "generic-lens" Data.Generics.Labels ()
  import GHC.Generics

  data Education = Degree Text | PhD Text | NoEducation

  schemaEducation = union'
    [ alt "NoEducation" #_NoEducation
    , alt "Degree"      #_Degree
    , alt "PhD"         #_PhD
    ]
  

Given a non empty set of tagged partial schemas, constructs the schema that applies them in order and selects the first successful match.

union' :: NonEmpty (UnionTag from) -> TypedSchema from Source #

Given a non empty set of constructors, construct the schema that selects the first matching constructor

alt :: HasSchema a => Text -> Prism' from a -> UnionTag from Source #

alt name prism introduces a discriminated union alternative with the default schema

altWith :: TypedSchema a -> Text -> Prism' from a -> UnionTag from Source #

altWith name prism schema introduces a discriminated union alternative

data UnionTag from Source #

Existential wrapper for convenient definition of discriminated unions

oneOf :: NonEmpty (TypedSchemaFlex from a) -> TypedSchemaFlex from a Source #

The schema of undiscriminated unions. Prefer using union where possible

Encoding

encode :: HasSchema a => a -> Value Source #

encode using the default schema

decode :: HasSchema a => Value -> Either [(Trace, DecodeError)] a Source #

Decode using the default schema.

encodeTo :: HasSchema a => Schema -> Either [(Trace, Mismatch)] (a -> Value) Source #

Attempt to encode to the target schema using the default schema. First encodes using the default schema, then computes a coercion applying isSubtypeOf, and then applies the coercion to the encoded data.

decodeFrom :: HasSchema a => Schema -> Either [(Trace, DecodeError)] (Value -> Either [(Trace, DecodeError)] a) Source #

Apply isSubtypeOf to construct a coercion from the source schema to the default schema, apply the coercion to the data, and attempt to decode using the default schema.

encodeWith :: TypedSchemaFlex from a -> from -> Value Source #

Given a typed schema, produce a JSON encoder to the firt version returned by extractSchema

decodeWith :: TypedSchemaFlex from a -> Value -> Either D a Source #

Given a JSON Value and a typed schema, extract a Haskell value

encodeToWith :: TypedSchemaFlex from a -> Schema -> Either E (from -> Value) Source #

Given source and target schemas, produce a JSON encoder

working with recursive schemas

named :: SchemaName -> TypedSchemaFlex from' a -> TypedSchemaFlex from' a Source #

named n sc annotates a schema with a name, allowing for circular schemas.

Untyped schemas

data Schema Source #

A schema for untyped data, such as JSON or XML.

Constructors

Array Schema 
StringMap Schema 
Enum (NonEmpty Text) 
Record (HashMap Text Field) 
OneOf (NonEmpty Schema)

Decoding works for all alternatives, encoding only for one

Prim Text

Carries the name of primitive type

Named SchemaName Schema 

Bundled Patterns

pattern Empty :: Schema 
pattern Union :: NonEmpty (Text, Schema) -> Schema 
Instances
Eq Schema Source # 
Instance details

Defined in Schemas.Untyped

Methods

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

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

Show Schema Source # 
Instance details

Defined in Schemas.Untyped

Generic Schema Source # 
Instance details

Defined in Schemas.Untyped

Associated Types

type Rep Schema :: Type -> Type #

Methods

from :: Schema -> Rep Schema x #

to :: Rep Schema x -> Schema #

Semigroup Schema Source # 
Instance details

Defined in Schemas.Untyped

Monoid Schema Source # 
Instance details

Defined in Schemas.Untyped

HasSchema Schema Source # 
Instance details

Defined in Schemas.Class

type Rep Schema Source # 
Instance details

Defined in Schemas.Untyped

data Field Source #

Constructors

Field 

Fields

Instances
Eq Field Source # 
Instance details

Defined in Schemas.Untyped

Methods

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

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

Show Field Source # 
Instance details

Defined in Schemas.Untyped

Methods

showsPrec :: Int -> Field -> ShowS #

show :: Field -> String #

showList :: [Field] -> ShowS #

Generic Field Source # 
Instance details

Defined in Schemas.Untyped

Associated Types

type Rep Field :: Type -> Type #

Methods

from :: Field -> Rep Field x #

to :: Rep Field x -> Field #

HasSchema Field Source # 
Instance details

Defined in Schemas.Class

type Rep Field Source # 
Instance details

Defined in Schemas.Untyped

type Rep Field = D1 (MetaData "Field" "Schemas.Untyped" "schemas-0.3.0.2-4dRbmaSzUQTEiuMmtXF3VD" False) (C1 (MetaCons "Field" PrefixI True) (S1 (MetaSel (Just "fieldSchema") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Schema) :*: S1 (MetaSel (Just "isRequired") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Bool)))

Extraction

extractSchema :: TypedSchemaFlex from a -> NonEmpty Schema Source #

Extract an untyped schema that can be serialized.

For schemas with alternatives, this enumerates all the possible versions lazily. Beware when using on schemas with multiple alternatives, as the number of versions is exponential.

theSchema :: forall a. HasSchema a => Schema Source #

Extract the default Schema for a type

Functions

type Trace = [Text] Source #

isSubtypeOf :: Validators -> Schema -> Schema -> Either [(Trace, Mismatch)] (Value -> Value) Source #

sub isSubtypeOf sup returns a witness that sub is a subtype of sup, i.e. a cast function sub -> sup

Array Bool `isSubtypeOf` Bool

Just function > Record [("a", Bool)] isSubtypeOf Record [("a", Number)] Nothing

coerce :: forall sub sup. (HasSchema sub, HasSchema sup) => Value -> Maybe Value Source #

Coerce from sub to supReturns Nothing if sub is not a subtype of sup

validate :: Validators -> Schema -> Value -> [(Trace, Mismatch)] Source #

Structural validation of a JSON value against a schema Ignores extraneous fields in records

Reexports

class Profunctor (p :: Type -> Type -> Type) where #

Formally, the class Profunctor represents a profunctor from Hask -> Hask.

Intuitively it is a bifunctor where the first argument is contravariant and the second argument is covariant.

You can define a Profunctor by either defining dimap or by defining both lmap and rmap.

If you supply dimap, you should ensure that:

dimap id idid

If you supply lmap and rmap, ensure:

lmap idid
rmap idid

If you supply both, you should also ensure:

dimap f g ≡ lmap f . rmap g

These ensure by parametricity:

dimap (f . g) (h . i) ≡ dimap g h . dimap f i
lmap (f . g) ≡ lmap g . lmap f
rmap (f . g) ≡ rmap f . rmap g

Minimal complete definition

dimap | lmap, rmap

Methods

dimap :: (a -> b) -> (c -> d) -> p b c -> p a d #

Map over both arguments at the same time.

dimap f g ≡ lmap f . rmap g

lmap :: (a -> b) -> p b c -> p a c #

Map the first argument contravariantly.

lmap f ≡ dimap f id

rmap :: (b -> c) -> p a b -> p a c #

Map the second argument covariantly.

rmapdimap id
Instances
Profunctor ReifiedGetter 
Instance details

Defined in Control.Lens.Reified

Methods

dimap :: (a -> b) -> (c -> d) -> ReifiedGetter b c -> ReifiedGetter a d #

lmap :: (a -> b) -> ReifiedGetter b c -> ReifiedGetter a c #

rmap :: (b -> c) -> ReifiedGetter a b -> ReifiedGetter a c #

(#.) :: Coercible c b => q b c -> ReifiedGetter a b -> ReifiedGetter a c #

(.#) :: Coercible b a => ReifiedGetter b c -> q a b -> ReifiedGetter a c #

Profunctor ReifiedFold 
Instance details

Defined in Control.Lens.Reified

Methods

dimap :: (a -> b) -> (c -> d) -> ReifiedFold b c -> ReifiedFold a d #

lmap :: (a -> b) -> ReifiedFold b c -> ReifiedFold a c #

rmap :: (b -> c) -> ReifiedFold a b -> ReifiedFold a c #

(#.) :: Coercible c b => q b c -> ReifiedFold a b -> ReifiedFold a c #

(.#) :: Coercible b a => ReifiedFold b c -> q a b -> ReifiedFold a c #

Profunctor RecordFields Source # 
Instance details

Defined in Schemas.Internal

Methods

dimap :: (a -> b) -> (c -> d) -> RecordFields b c -> RecordFields a d #

lmap :: (a -> b) -> RecordFields b c -> RecordFields a c #

rmap :: (b -> c) -> RecordFields a b -> RecordFields a c #

(#.) :: Coercible c b => q b c -> RecordFields a b -> RecordFields a c #

(.#) :: Coercible b a => RecordFields b c -> q a b -> RecordFields a c #

Profunctor RecordField Source # 
Instance details

Defined in Schemas.Internal

Methods

dimap :: (a -> b) -> (c -> d) -> RecordField b c -> RecordField a d #

lmap :: (a -> b) -> RecordField b c -> RecordField a c #

rmap :: (b -> c) -> RecordField a b -> RecordField a c #

(#.) :: Coercible c b => q b c -> RecordField a b -> RecordField a c #

(.#) :: Coercible b a => RecordField b c -> q a b -> RecordField a c #

Profunctor TypedSchemaFlex Source # 
Instance details

Defined in Schemas.Internal

Methods

dimap :: (a -> b) -> (c -> d) -> TypedSchemaFlex b c -> TypedSchemaFlex a d #

lmap :: (a -> b) -> TypedSchemaFlex b c -> TypedSchemaFlex a c #

rmap :: (b -> c) -> TypedSchemaFlex a b -> TypedSchemaFlex a c #

(#.) :: Coercible c b => q b c -> TypedSchemaFlex a b -> TypedSchemaFlex a c #

(.#) :: Coercible b a => TypedSchemaFlex b c -> q a b -> TypedSchemaFlex a c #

Monad m => Profunctor (Kleisli m) 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> Kleisli m b c -> Kleisli m a d #

lmap :: (a -> b) -> Kleisli m b c -> Kleisli m a c #

rmap :: (b -> c) -> Kleisli m a b -> Kleisli m a c #

(#.) :: Coercible c b => q b c -> Kleisli m a b -> Kleisli m a c #

(.#) :: Coercible b a => Kleisli m b c -> q a b -> Kleisli m a c #

Profunctor (ReifiedIndexedGetter i) 
Instance details

Defined in Control.Lens.Reified

Methods

dimap :: (a -> b) -> (c -> d) -> ReifiedIndexedGetter i b c -> ReifiedIndexedGetter i a d #

lmap :: (a -> b) -> ReifiedIndexedGetter i b c -> ReifiedIndexedGetter i a c #

rmap :: (b -> c) -> ReifiedIndexedGetter i a b -> ReifiedIndexedGetter i a c #

(#.) :: Coercible c b => q b c -> ReifiedIndexedGetter i a b -> ReifiedIndexedGetter i a c #

(.#) :: Coercible b a => ReifiedIndexedGetter i b c -> q a b -> ReifiedIndexedGetter i a c #

Profunctor (ReifiedIndexedFold i) 
Instance details

Defined in Control.Lens.Reified

Methods

dimap :: (a -> b) -> (c -> d) -> ReifiedIndexedFold i b c -> ReifiedIndexedFold i a d #

lmap :: (a -> b) -> ReifiedIndexedFold i b c -> ReifiedIndexedFold i a c #

rmap :: (b -> c) -> ReifiedIndexedFold i a b -> ReifiedIndexedFold i a c #

(#.) :: Coercible c b => q b c -> ReifiedIndexedFold i a b -> ReifiedIndexedFold i a c #

(.#) :: Coercible b a => ReifiedIndexedFold i b c -> q a b -> ReifiedIndexedFold i a c #

Profunctor (Indexed i) 
Instance details

Defined in Control.Lens.Internal.Indexed

Methods

dimap :: (a -> b) -> (c -> d) -> Indexed i b c -> Indexed i a d #

lmap :: (a -> b) -> Indexed i b c -> Indexed i a c #

rmap :: (b -> c) -> Indexed i a b -> Indexed i a c #

(#.) :: Coercible c b => q b c -> Indexed i a b -> Indexed i a c #

(.#) :: Coercible b a => Indexed i b c -> q a b -> Indexed i a c #

Profunctor p => Profunctor (CofreeMapping p) 
Instance details

Defined in Data.Profunctor.Mapping

Methods

dimap :: (a -> b) -> (c -> d) -> CofreeMapping p b c -> CofreeMapping p a d #

lmap :: (a -> b) -> CofreeMapping p b c -> CofreeMapping p a c #

rmap :: (b -> c) -> CofreeMapping p a b -> CofreeMapping p a c #

(#.) :: Coercible c b => q b c -> CofreeMapping p a b -> CofreeMapping p a c #

(.#) :: Coercible b a => CofreeMapping p b c -> q a b -> CofreeMapping p a c #

Profunctor (FreeMapping p) 
Instance details

Defined in Data.Profunctor.Mapping

Methods

dimap :: (a -> b) -> (c -> d) -> FreeMapping p b c -> FreeMapping p a d #

lmap :: (a -> b) -> FreeMapping p b c -> FreeMapping p a c #

rmap :: (b -> c) -> FreeMapping p a b -> FreeMapping p a c #

(#.) :: Coercible c b => q b c -> FreeMapping p a b -> FreeMapping p a c #

(.#) :: Coercible b a => FreeMapping p b c -> q a b -> FreeMapping p a c #

Profunctor p => Profunctor (TambaraSum p) 
Instance details

Defined in Data.Profunctor.Choice

Methods

dimap :: (a -> b) -> (c -> d) -> TambaraSum p b c -> TambaraSum p a d #

lmap :: (a -> b) -> TambaraSum p b c -> TambaraSum p a c #

rmap :: (b -> c) -> TambaraSum p a b -> TambaraSum p a c #

(#.) :: Coercible c b => q b c -> TambaraSum p a b -> TambaraSum p a c #

(.#) :: Coercible b a => TambaraSum p b c -> q a b -> TambaraSum p a c #

Profunctor (PastroSum p) 
Instance details

Defined in Data.Profunctor.Choice

Methods

dimap :: (a -> b) -> (c -> d) -> PastroSum p b c -> PastroSum p a d #

lmap :: (a -> b) -> PastroSum p b c -> PastroSum p a c #

rmap :: (b -> c) -> PastroSum p a b -> PastroSum p a c #

(#.) :: Coercible c b => q b c -> PastroSum p a b -> PastroSum p a c #

(.#) :: Coercible b a => PastroSum p b c -> q a b -> PastroSum p a c #

Profunctor (CotambaraSum p) 
Instance details

Defined in Data.Profunctor.Choice

Methods

dimap :: (a -> b) -> (c -> d) -> CotambaraSum p b c -> CotambaraSum p a d #

lmap :: (a -> b) -> CotambaraSum p b c -> CotambaraSum p a c #

rmap :: (b -> c) -> CotambaraSum p a b -> CotambaraSum p a c #

(#.) :: Coercible c b => q b c -> CotambaraSum p a b -> CotambaraSum p a c #

(.#) :: Coercible b a => CotambaraSum p b c -> q a b -> CotambaraSum p a c #

Profunctor (CopastroSum p) 
Instance details

Defined in Data.Profunctor.Choice

Methods

dimap :: (a -> b) -> (c -> d) -> CopastroSum p b c -> CopastroSum p a d #

lmap :: (a -> b) -> CopastroSum p b c -> CopastroSum p a c #

rmap :: (b -> c) -> CopastroSum p a b -> CopastroSum p a c #

(#.) :: Coercible c b => q b c -> CopastroSum p a b -> CopastroSum p a c #

(.#) :: Coercible b a => CopastroSum p b c -> q a b -> CopastroSum p a c #

Profunctor p => Profunctor (Closure p) 
Instance details

Defined in Data.Profunctor.Closed

Methods

dimap :: (a -> b) -> (c -> d) -> Closure p b c -> Closure p a d #

lmap :: (a -> b) -> Closure p b c -> Closure p a c #

rmap :: (b -> c) -> Closure p a b -> Closure p a c #

(#.) :: Coercible c b => q b c -> Closure p a b -> Closure p a c #

(.#) :: Coercible b a => Closure p b c -> q a b -> Closure p a c #

Profunctor (Environment p) 
Instance details

Defined in Data.Profunctor.Closed

Methods

dimap :: (a -> b) -> (c -> d) -> Environment p b c -> Environment p a d #

lmap :: (a -> b) -> Environment p b c -> Environment p a c #

rmap :: (b -> c) -> Environment p a b -> Environment p a c #

(#.) :: Coercible c b => q b c -> Environment p a b -> Environment p a c #

(.#) :: Coercible b a => Environment p b c -> q a b -> Environment p a c #

Profunctor p => Profunctor (Tambara p) 
Instance details

Defined in Data.Profunctor.Strong

Methods

dimap :: (a -> b) -> (c -> d) -> Tambara p b c -> Tambara p a d #

lmap :: (a -> b) -> Tambara p b c -> Tambara p a c #

rmap :: (b -> c) -> Tambara p a b -> Tambara p a c #

(#.) :: Coercible c b => q b c -> Tambara p a b -> Tambara p a c #

(.#) :: Coercible b a => Tambara p b c -> q a b -> Tambara p a c #

Profunctor (Pastro p) 
Instance details

Defined in Data.Profunctor.Strong

Methods

dimap :: (a -> b) -> (c -> d) -> Pastro p b c -> Pastro p a d #

lmap :: (a -> b) -> Pastro p b c -> Pastro p a c #

rmap :: (b -> c) -> Pastro p a b -> Pastro p a c #

(#.) :: Coercible c b => q b c -> Pastro p a b -> Pastro p a c #

(.#) :: Coercible b a => Pastro p b c -> q a b -> Pastro p a c #

Profunctor (Cotambara p) 
Instance details

Defined in Data.Profunctor.Strong

Methods

dimap :: (a -> b) -> (c -> d) -> Cotambara p b c -> Cotambara p a d #

lmap :: (a -> b) -> Cotambara p b c -> Cotambara p a c #

rmap :: (b -> c) -> Cotambara p a b -> Cotambara p a c #

(#.) :: Coercible c b => q b c -> Cotambara p a b -> Cotambara p a c #

(.#) :: Coercible b a => Cotambara p b c -> q a b -> Cotambara p a c #

Profunctor (Copastro p) 
Instance details

Defined in Data.Profunctor.Strong

Methods

dimap :: (a -> b) -> (c -> d) -> Copastro p b c -> Copastro p a d #

lmap :: (a -> b) -> Copastro p b c -> Copastro p a c #

rmap :: (b -> c) -> Copastro p a b -> Copastro p a c #

(#.) :: Coercible c b => q b c -> Copastro p a b -> Copastro p a c #

(.#) :: Coercible b a => Copastro p b c -> q a b -> Copastro p a c #

Functor f => Profunctor (Star f) 
Instance details

Defined in Data.Profunctor.Types

Methods

dimap :: (a -> b) -> (c -> d) -> Star f b c -> Star f a d #

lmap :: (a -> b) -> Star f b c -> Star f a c #

rmap :: (b -> c) -> Star f a b -> Star f a c #

(#.) :: Coercible c b => q b c -> Star f a b -> Star f a c #

(.#) :: Coercible b a => Star f b c -> q a b -> Star f a c #

Functor f => Profunctor (Costar f) 
Instance details

Defined in Data.Profunctor.Types

Methods

dimap :: (a -> b) -> (c -> d) -> Costar f b c -> Costar f a d #

lmap :: (a -> b) -> Costar f b c -> Costar f a c #

rmap :: (b -> c) -> Costar f a b -> Costar f a c #

(#.) :: Coercible c b => q b c -> Costar f a b -> Costar f a c #

(.#) :: Coercible b a => Costar f b c -> q a b -> Costar f a c #

Arrow p => Profunctor (WrappedArrow p) 
Instance details

Defined in Data.Profunctor.Types

Methods

dimap :: (a -> b) -> (c -> d) -> WrappedArrow p b c -> WrappedArrow p a d #

lmap :: (a -> b) -> WrappedArrow p b c -> WrappedArrow p a c #

rmap :: (b -> c) -> WrappedArrow p a b -> WrappedArrow p a c #

(#.) :: Coercible c b => q b c -> WrappedArrow p a b -> WrappedArrow p a c #

(.#) :: Coercible b a => WrappedArrow p b c -> q a b -> WrappedArrow p a c #

Profunctor (Forget r) 
Instance details

Defined in Data.Profunctor.Types

Methods

dimap :: (a -> b) -> (c -> d) -> Forget r b c -> Forget r a d #

lmap :: (a -> b) -> Forget r b c -> Forget r a c #

rmap :: (b -> c) -> Forget r a b -> Forget r a c #

(#.) :: Coercible c b => q b c -> Forget r a b -> Forget r a c #

(.#) :: Coercible b a => Forget r b c -> q a b -> Forget r a c #

Profunctor (Tagged :: Type -> Type -> Type) 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> Tagged b c -> Tagged a d #

lmap :: (a -> b) -> Tagged b c -> Tagged a c #

rmap :: (b -> c) -> Tagged a b -> Tagged a c #

(#.) :: Coercible c b => q b c -> Tagged a b -> Tagged a c #

(.#) :: Coercible b a => Tagged b c -> q a b -> Tagged a c #

Profunctor ((->) :: Type -> Type -> Type) 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> (b -> c) -> a -> d #

lmap :: (a -> b) -> (b -> c) -> a -> c #

rmap :: (b -> c) -> (a -> b) -> a -> c #

(#.) :: Coercible c b => q b c -> (a -> b) -> a -> c #

(.#) :: Coercible b a => (b -> c) -> q a b -> a -> c #

Functor w => Profunctor (Cokleisli w) 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> Cokleisli w b c -> Cokleisli w a d #

lmap :: (a -> b) -> Cokleisli w b c -> Cokleisli w a c #

rmap :: (b -> c) -> Cokleisli w a b -> Cokleisli w a c #

(#.) :: Coercible c b => q b c -> Cokleisli w a b -> Cokleisli w a c #

(.#) :: Coercible b a => Cokleisli w b c -> q a b -> Cokleisli w a c #

Profunctor (Market a b) 
Instance details

Defined in Control.Lens.Internal.Prism

Methods

dimap :: (a0 -> b0) -> (c -> d) -> Market a b b0 c -> Market a b a0 d #

lmap :: (a0 -> b0) -> Market a b b0 c -> Market a b a0 c #

rmap :: (b0 -> c) -> Market a b a0 b0 -> Market a b a0 c #

(#.) :: Coercible c b0 => q b0 c -> Market a b a0 b0 -> Market a b a0 c #

(.#) :: Coercible b0 a0 => Market a b b0 c -> q a0 b0 -> Market a b a0 c #

Profunctor (Exchange a b) 
Instance details

Defined in Control.Lens.Internal.Iso

Methods

dimap :: (a0 -> b0) -> (c -> d) -> Exchange a b b0 c -> Exchange a b a0 d #

lmap :: (a0 -> b0) -> Exchange a b b0 c -> Exchange a b a0 c #

rmap :: (b0 -> c) -> Exchange a b a0 b0 -> Exchange a b a0 c #

(#.) :: Coercible c b0 => q b0 c -> Exchange a b a0 b0 -> Exchange a b a0 c #

(.#) :: Coercible b0 a0 => Exchange a b b0 c -> q a0 b0 -> Exchange a b a0 c #

(Profunctor p, Profunctor q) => Profunctor (Procompose p q) 
Instance details

Defined in Data.Profunctor.Composition

Methods

dimap :: (a -> b) -> (c -> d) -> Procompose p q b c -> Procompose p q a d #

lmap :: (a -> b) -> Procompose p q b c -> Procompose p q a c #

rmap :: (b -> c) -> Procompose p q a b -> Procompose p q a c #

(#.) :: Coercible c b => q0 b c -> Procompose p q a b -> Procompose p q a c #

(.#) :: Coercible b a => Procompose p q b c -> q0 a b -> Procompose p q a c #

(Profunctor p, Profunctor q) => Profunctor (Rift p q) 
Instance details

Defined in Data.Profunctor.Composition

Methods

dimap :: (a -> b) -> (c -> d) -> Rift p q b c -> Rift p q a d #

lmap :: (a -> b) -> Rift p q b c -> Rift p q a c #

rmap :: (b -> c) -> Rift p q a b -> Rift p q a c #

(#.) :: Coercible c b => q0 b c -> Rift p q a b -> Rift p q a c #

(.#) :: Coercible b a => Rift p q b c -> q0 a b -> Rift p q a c #

Functor f => Profunctor (Joker f :: Type -> Type -> Type) 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> Joker f b c -> Joker f a d #

lmap :: (a -> b) -> Joker f b c -> Joker f a c #

rmap :: (b -> c) -> Joker f a b -> Joker f a c #

(#.) :: Coercible c b => q b c -> Joker f a b -> Joker f a c #

(.#) :: Coercible b a => Joker f b c -> q a b -> Joker f a c #

Contravariant f => Profunctor (Clown f :: Type -> Type -> Type) 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> Clown f b c -> Clown f a d #

lmap :: (a -> b) -> Clown f b c -> Clown f a c #

rmap :: (b -> c) -> Clown f a b -> Clown f a c #

(#.) :: Coercible c b => q b c -> Clown f a b -> Clown f a c #

(.#) :: Coercible b a => Clown f b c -> q a b -> Clown f a c #

(Profunctor p, Profunctor q) => Profunctor (Sum p q) 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> Sum p q b c -> Sum p q a d #

lmap :: (a -> b) -> Sum p q b c -> Sum p q a c #

rmap :: (b -> c) -> Sum p q a b -> Sum p q a c #

(#.) :: Coercible c b => q0 b c -> Sum p q a b -> Sum p q a c #

(.#) :: Coercible b a => Sum p q b c -> q0 a b -> Sum p q a c #

(Profunctor p, Profunctor q) => Profunctor (Product p q) 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> Product p q b c -> Product p q a d #

lmap :: (a -> b) -> Product p q b c -> Product p q a c #

rmap :: (b -> c) -> Product p q a b -> Product p q a c #

(#.) :: Coercible c b => q0 b c -> Product p q a b -> Product p q a c #

(.#) :: Coercible b a => Product p q b c -> q0 a b -> Product p q a c #

(Functor f, Profunctor p) => Profunctor (Tannen f p) 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> Tannen f p b c -> Tannen f p a d #

lmap :: (a -> b) -> Tannen f p b c -> Tannen f p a c #

rmap :: (b -> c) -> Tannen f p a b -> Tannen f p a c #

(#.) :: Coercible c b => q b c -> Tannen f p a b -> Tannen f p a c #

(.#) :: Coercible b a => Tannen f p b c -> q a b -> Tannen f p a c #

(Profunctor p, Functor f, Functor g) => Profunctor (Biff p f g) 
Instance details

Defined in Data.Profunctor.Unsafe

Methods

dimap :: (a -> b) -> (c -> d) -> Biff p f g b c -> Biff p f g a d #

lmap :: (a -> b) -> Biff p f g b c -> Biff p f g a c #

rmap :: (b -> c) -> Biff p f g a b -> Biff p f g a c #

(#.) :: Coercible c b => q b c -> Biff p f g a b -> Biff p f g a c #

(.#) :: Coercible b a => Biff p f g b c -> q a b -> Biff p f g a c #