lazify-0.1.0.1: A simple utility for lazy record matching
Safe HaskellNone
LanguageHaskell2010

Data.Lazify.Internal

Description

Record types in Haskell can be made lazy through lazy pattern matching. This module offers functions for making them lazy generically.

Synopsis

Documentation

class Lazifiable a where Source #

A class for types that can be lazified. A generic default is provided for convenience. To lazify a type using its generic representation, use genericLazify.

Minimal complete definition

Nothing

Methods

lazify :: a -> a Source #

Lazily rewrap a record. Applying lazify to a record and then pattern matching on it strictly is equivalent to pattern matching on it lazily.

strictFirst :: (a -> a') -> (a, b) -> (a', b)
strictFirst f (a, b) = (f a, b)

lazyFirst :: (a -> a') -> (a, b) -> (a', b)
lazyFirst f = strictFirst f . lazify
-- Equivalently
lazyFirst f ~(a, b) = (f a, b)

default lazify :: (Generic a, GLazifiable a (Rep a)) => a -> a Source #

Instances

Instances details
Lazifiable () Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: () -> () Source #

Lazifiable a => Lazifiable (Min a) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: Min a -> Min a Source #

Lazifiable a => Lazifiable (Max a) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: Max a -> Max a Source #

Lazifiable a => Lazifiable (First a) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: First a -> First a Source #

Lazifiable a => Lazifiable (Last a) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: Last a -> Last a Source #

Lazifiable a => Lazifiable (WrappedMonoid a) Source # 
Instance details

Defined in Data.Lazify.Internal

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

Defined in Data.Lazify.Internal

Methods

lazify :: Identity a -> Identity a Source #

Lazifiable a => Lazifiable (Dual a) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: Dual a -> Dual a Source #

Lazifiable a => Lazifiable (Sum a) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: Sum a -> Sum a Source #

Lazifiable a => Lazifiable (Product a) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: Product a -> Product a Source #

Lazifiable (NonEmpty a) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: NonEmpty a -> NonEmpty a Source #

Lazifiable (Tree a) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: Tree a -> Tree a Source #

Typeable a => Lazifiable (TypeRep a) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: TypeRep a -> TypeRep a Source #

Lazifiable (a, b) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: (a, b) -> (a, b) Source #

Lazifiable (Arg a b) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: Arg a b -> Arg a b Source #

Lazifiable (Proxy a) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: Proxy a -> Proxy a Source #

Lazifiable (a, b, c) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: (a, b, c) -> (a, b, c) Source #

Lazifiable a => Lazifiable (Const a b) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: Const a b -> Const a b Source #

Lazifiable (f a) => Lazifiable (Ap f a) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: Ap f a -> Ap f a Source #

Lazifiable (f a) => Lazifiable (Alt f a) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: Alt f a -> Alt f a Source #

Coercible a b => Lazifiable (Coercion a b) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: Coercion a b -> Coercion a b Source #

a ~ b => Lazifiable (a :~: b) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: (a :~: b) -> a :~: b Source #

Lazifiable b => Lazifiable (Tagged a b) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: Tagged a b -> Tagged a b Source #

Lazifiable (t a) => Lazifiable (Reverse t a) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: Reverse t a -> Reverse t a Source #

Lazifiable (f a) => Lazifiable (IdentityT f a) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: IdentityT f a -> IdentityT f a Source #

Lazifiable (f a) => Lazifiable (Backwards f a) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: Backwards f a -> Backwards f a Source #

Lazifiable (a, b, c, d) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: (a, b, c, d) -> (a, b, c, d) Source #

Lazifiable (Product f g a) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: Product f g a -> Product f g a Source #

a ~~ b => Lazifiable (a :~~: b) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: (a :~~: b) -> a :~~: b Source #

Lazifiable (f (g a)) => Lazifiable ((f :.: g) a) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: (f :.: g) a -> (f :.: g) a Source #

Lazifiable (a, b, c, d, e) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: (a, b, c, d, e) -> (a, b, c, d, e) Source #

Lazifiable (f (g a)) => Lazifiable (Compose f g a) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: Compose f g a -> Compose f g a Source #

Lazifiable (a, b, c, d, e, f) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: (a, b, c, d, e, f) -> (a, b, c, d, e, f) Source #

Lazifiable (a, b, c, d, e, f, g) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: (a, b, c, d, e, f, g) -> (a, b, c, d, e, f, g) Source #

Lazifiable (a, b, c, d, e, f, g, h) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: (a, b, c, d, e, f, g, h) -> (a, b, c, d, e, f, g, h) Source #

Lazifiable (a, b, c, d, e, f, g, h, i) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: (a, b, c, d, e, f, g, h, i) -> (a, b, c, d, e, f, g, h, i) Source #

Lazifiable (a, b, c, d, e, f, g, h, i, j) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

lazify :: (a, b, c, d, e, f, g, h, i, j) -> (a, b, c, d, e, f, g, h, i, j) Source #

class GLazifiable a f where Source #

A Generic representation that can be lazified.

Methods

glazify :: f p -> f p Source #

Lazify a Generic representation.

Instances

Instances details
GLazifiable (a :: k1) (U1 :: k2 -> Type) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

glazify :: forall (p :: k). U1 p -> U1 p Source #

(TypeError ((('Text "Can't lazify " :<>: 'ShowType a) :<>: 'Text ":") :$$: 'Text "It is a sum type.") :: Constraint) => GLazifiable (a :: k1) (f :+: g :: k2 -> Type) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

glazify :: forall (p :: k). (f :+: g) p -> (f :+: g) p Source #

(GLazifiable a f, GLazifiable a g) => GLazifiable (a :: k1) (f :*: g :: k2 -> Type) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

glazify :: forall (p :: k). (f :*: g) p -> (f :*: g) p Source #

GLazifiable (a :: k1) (K1 i c :: k2 -> Type) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

glazify :: forall (p :: k). K1 i c p -> K1 i c p Source #

(TypeError ((('Text "Can't lazify " :<>: 'ShowType a) :<>: 'Text ":") :$$: 'Text "It has a strict (unpacked) field.") :: Constraint) => GLazifiable (a :: k1) (S1 ('MetaSel _p _q _r 'DecidedUnpack) f :: k2 -> Type) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

glazify :: forall (p :: k). S1 ('MetaSel _p _q _r 'DecidedUnpack) f p -> S1 ('MetaSel _p _q _r 'DecidedUnpack) f p Source #

(TypeError ((('Text "Can't lazify " :<>: 'ShowType a) :<>: 'Text ":") :$$: 'Text "It has a strict field.") :: Constraint) => GLazifiable (a :: k1) (S1 ('MetaSel _p _q _r 'DecidedStrict) f :: k2 -> Type) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

glazify :: forall (p :: k). S1 ('MetaSel _p _q _r 'DecidedStrict) f p -> S1 ('MetaSel _p _q _r 'DecidedStrict) f p Source #

GLazifiable a f => GLazifiable (a :: k1) (S1 ('MetaSel _p _q _r 'DecidedLazy) f :: k2 -> Type) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

glazify :: forall (p :: k). S1 ('MetaSel _p _q _r 'DecidedLazy) f p -> S1 ('MetaSel _p _q _r 'DecidedLazy) f p Source #

GLazifiable a f => GLazifiable (a :: k1) (C1 c f :: k2 -> Type) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

glazify :: forall (p :: k). C1 c f p -> C1 c f p Source #

GLazifiable a f => GLazifiable (a :: k1) (D1 ('MetaData x y z 'False) f :: k2 -> Type) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

glazify :: forall (p :: k). D1 ('MetaData x y z 'False) f p -> D1 ('MetaData x y z 'False) f p Source #

Lazifiable c => GLazifiable (a :: k1) (D1 ('MetaData x y z 'True) (C1 _m (S1 _o (Rec0 c))) :: k2 -> Type) Source # 
Instance details

Defined in Data.Lazify.Internal

Methods

glazify :: forall (p :: k). D1 ('MetaData x y z 'True) (C1 _m (S1 _o (Rec0 c))) p -> D1 ('MetaData x y z 'True) (C1 _m (S1 _o (Rec0 c))) p Source #

genericLazify :: forall a. (Generic a, GLazifiable a (Rep a)) => a -> a Source #

Lazify a record using its generic representation.

Note that newtypes are treated specially: a newtype is lazified by lazifying its underlying type using its Lazifiable instance.

($~) :: forall rep a (b :: TYPE rep). Lazifiable a => (a -> b) -> a -> b Source #

Apply a function to a lazified value.

Note to users of TypeApplications: For GHC >= 9.0.1, the representation is marked as inferred. Before that, doing so is impossible and the representation must be passed as the first type argument. I'm sorry.