lazify-0.1.0.0: 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.

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)

lazify :: (Generic a, GLazifiable (Rep a)) => 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)

Instances

Lazifiable () Source # 

Methods

lazify :: () -> () Source #

Lazifiable a => Lazifiable (Min a) Source # 

Methods

lazify :: Min a -> Min a Source #

Lazifiable a => Lazifiable (Max a) Source # 

Methods

lazify :: Max a -> Max a Source #

Lazifiable a => Lazifiable (First a) Source # 

Methods

lazify :: First a -> First a Source #

Lazifiable a => Lazifiable (Last a) Source # 

Methods

lazify :: Last a -> Last a Source #

Lazifiable a => Lazifiable (Identity a) Source # 

Methods

lazify :: Identity a -> Identity a Source #

Lazifiable a => Lazifiable (Sum a) Source # 

Methods

lazify :: Sum a -> Sum a Source #

Lazifiable a => Lazifiable (Product a) Source # 

Methods

lazify :: Product a -> Product a Source #

Typeable k a => Lazifiable (TypeRep k a) Source # 

Methods

lazify :: TypeRep k a -> TypeRep k a Source #

Lazifiable (a, b) Source # 

Methods

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

Lazifiable (Arg a b) Source # 

Methods

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

Lazifiable (Proxy k a) Source # 

Methods

lazify :: Proxy k a -> Proxy k a Source #

Lazifiable (a, b, c) Source # 

Methods

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

Lazifiable a => Lazifiable (Const k a b) Source # 

Methods

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

Lazifiable (f a) => Lazifiable (Alt k f a) Source # 

Methods

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

Coercible k a b => Lazifiable (Coercion k a b) Source # 

Methods

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

(~) k a b => Lazifiable ((:~:) k a b) Source # 

Methods

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

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

Methods

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

Lazifiable (Product k f g a) Source # 

Methods

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

(~~) k1 k2 a b => Lazifiable ((:~~:) k1 k2 a b) Source # 

Methods

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

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

Methods

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

Lazifiable (f (g a)) => Lazifiable (Compose k k1 f g a) Source # 

Methods

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

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

Methods

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

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

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 # 

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 # 

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 # 

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 f where Source #

A Generic representation that can be lazified.

Minimal complete definition

glazify

Methods

glazify :: f a -> f a Source #

Lazify a Generic representation.

Instances

GLazifiable k (U1 k) Source # 

Methods

glazify :: f a -> f a Source #

(GLazifiable k f, GLazifiable k g) => GLazifiable k ((:*:) k f g) Source # 

Methods

glazify :: f a -> f a Source #

GLazifiable k (K1 k i c) Source # 

Methods

glazify :: f a -> f a Source #

GLazifiable k f => GLazifiable k (S1 k c f) Source # 

Methods

glazify :: f a -> f a Source #

GLazifiable k f => GLazifiable k (C1 k c f) Source # 

Methods

glazify :: f a -> f a Source #

GLazifiable k f => GLazifiable k (D1 k (MetaData x y z False) f) Source # 

Methods

glazify :: f a -> f a Source #

GIsNewtype k f => GLazifiable k (D1 k (MetaData x y z True) f) Source # 

Methods

glazify :: f a -> f a Source #

class GIsNewtype f where Source #

A Generic representation that should be lazified newtype-style. That is, its contents should be lazified.

Minimal complete definition

glazifyNewtype

Methods

glazifyNewtype :: f a -> f a Source #

Find the newtype payload and lazify it.

Instances

Lazifiable a => GIsNewtype k (K1 k i a) Source # 

Methods

glazifyNewtype :: f a -> f a Source #

GIsNewtype k f => GIsNewtype k (M1 k i c f) Source # 

Methods

glazifyNewtype :: f a -> f a Source #

genericLazify :: (Generic a, GLazifiable (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.