extensible-0.4.1: Extensible, efficient, optics-friendly data types and effects

Copyright(c) Fumiaki Kinoshita 2017
LicenseBSD3
MaintainerFumiaki Kinoshita <fumiexcel@gmail.com>
Safe HaskellSafe
LanguageHaskell2010

Data.Extensible.Wrapper

Description

 

Synopsis

Documentation

class Wrapper h where Source #

The extensible data types should take k -> * as a parameter. This class allows us to take a shortcut for direct representation.

Associated Types

type Repr h (v :: k) :: * Source #

Repr h v is the actual representation of h v.

Methods

_Wrapper :: (Functor f, Profunctor p) => Optic' p f (h v) (Repr h v) Source #

This is an isomorphism between h v and Repr h v.

_Wrapper :: Iso' (h v) (Repr h v)

Instances

Wrapper k (Proxy k) Source # 

Associated Types

type Repr (Proxy k) (h :: Proxy k -> *) (v :: Proxy k) :: * Source #

Methods

_Wrapper :: (Functor f, Profunctor p) => Optic' * * p f (h v) (Repr (Proxy k) h v) Source #

Wrapper k (Const' k a) Source # 

Associated Types

type Repr (Const' k a) (h :: Const' k a -> *) (v :: Const' k a) :: * Source #

Methods

_Wrapper :: (Functor f, Profunctor p) => Optic' * * p f (h v) (Repr (Const' k a) h v) Source #

Wrapper k h => Wrapper k (Nullable k h) Source # 

Associated Types

type Repr (Nullable k h) (h :: Nullable k h -> *) (v :: Nullable k h) :: * Source #

Methods

_Wrapper :: (Functor f, Profunctor p) => Optic' * * p f (h v) (Repr (Nullable k h) h v) Source #

Wrapper k h => Wrapper k (Match k h r) Source # 

Associated Types

type Repr (Match k h r) (h :: Match k h r -> *) (v :: Match k h r) :: * Source #

Methods

_Wrapper :: (Functor f, Profunctor p) => Optic' * * p f (h v) (Repr (Match k h r) h v) Source #

(Functor f, Wrapper k g) => Wrapper k (Comp k * f g) Source # 

Associated Types

type Repr (Comp k * f g) (h :: Comp k * f g -> *) (v :: Comp k * f g) :: * Source #

Methods

_Wrapper :: (Functor f, Profunctor p) => Optic' * * p f (h v) (Repr (Comp k * f g) h v) Source #

Wrapper * [] Source # 

Associated Types

type Repr [] (h :: [] -> *) (v :: []) :: * Source #

Methods

_Wrapper :: (Functor f, Profunctor p) => Optic' * * p f (h v) (Repr [] h v) Source #

Wrapper * Maybe Source # 

Associated Types

type Repr Maybe (h :: Maybe -> *) (v :: Maybe) :: * Source #

Methods

_Wrapper :: (Functor f, Profunctor p) => Optic' * * p f (h v) (Repr Maybe h v) Source #

Wrapper * Identity Source # 

Associated Types

type Repr Identity (h :: Identity -> *) (v :: Identity) :: * Source #

Methods

_Wrapper :: (Functor f, Profunctor p) => Optic' * * p f (h v) (Repr Identity h v) Source #

Wrapper v h => Wrapper (Assoc k v) (Field k v h) Source # 

Associated Types

type Repr (Field k v h) (h :: Field k v h -> *) (v :: Field k v h) :: * Source #

Methods

_Wrapper :: (Functor f, Profunctor p) => Optic' * * p f (h v) (Repr (Field k v h) h v) Source #

_WrapperAs :: (Functor f, Profunctor p, Wrapper h) => proxy v -> Optic' p f (h v) (Repr h v) Source #

Restricted version of _Wrapper. It is useful for eliminating ambiguousness.

newtype Const' a x Source #

Poly-kinded Const

Constructors

Const' 

Fields

Instances

Wrapper k (Const' k a) Source # 

Associated Types

type Repr (Const' k a) (h :: Const' k a -> *) (v :: Const' k a) :: * Source #

Methods

_Wrapper :: (Functor f, Profunctor p) => Optic' * * p f (h v) (Repr (Const' k a) h v) Source #

Eq a => Eq (Const' k a x) Source # 

Methods

(==) :: Const' k a x -> Const' k a x -> Bool #

(/=) :: Const' k a x -> Const' k a x -> Bool #

Ord a => Ord (Const' k a x) Source # 

Methods

compare :: Const' k a x -> Const' k a x -> Ordering #

(<) :: Const' k a x -> Const' k a x -> Bool #

(<=) :: Const' k a x -> Const' k a x -> Bool #

(>) :: Const' k a x -> Const' k a x -> Bool #

(>=) :: Const' k a x -> Const' k a x -> Bool #

max :: Const' k a x -> Const' k a x -> Const' k a x #

min :: Const' k a x -> Const' k a x -> Const' k a x #

Show a => Show (Const' k a x) Source # 

Methods

showsPrec :: Int -> Const' k a x -> ShowS #

show :: Const' k a x -> String #

showList :: [Const' k a x] -> ShowS #

type Repr k (Const' k a) b Source # 
type Repr k (Const' k a) b = a

newtype Comp f g a Source #

Poly-kinded composition

Constructors

Comp 

Fields

Instances

(Functor f, Wrapper k g) => Wrapper k (Comp k * f g) Source # 

Associated Types

type Repr (Comp k * f g) (h :: Comp k * f g -> *) (v :: Comp k * f g) :: * Source #

Methods

_Wrapper :: (Functor f, Profunctor p) => Optic' * * p f (h v) (Repr (Comp k * f g) h v) Source #

Eq (f (g a)) => Eq (Comp i j f g a) Source # 

Methods

(==) :: Comp i j f g a -> Comp i j f g a -> Bool #

(/=) :: Comp i j f g a -> Comp i j f g a -> Bool #

Ord (f (g a)) => Ord (Comp i j f g a) Source # 

Methods

compare :: Comp i j f g a -> Comp i j f g a -> Ordering #

(<) :: Comp i j f g a -> Comp i j f g a -> Bool #

(<=) :: Comp i j f g a -> Comp i j f g a -> Bool #

(>) :: Comp i j f g a -> Comp i j f g a -> Bool #

(>=) :: Comp i j f g a -> Comp i j f g a -> Bool #

max :: Comp i j f g a -> Comp i j f g a -> Comp i j f g a #

min :: Comp i j f g a -> Comp i j f g a -> Comp i j f g a #

Show (f (g a)) => Show (Comp i j f g a) Source # 

Methods

showsPrec :: Int -> Comp i j f g a -> ShowS #

show :: Comp i j f g a -> String #

showList :: [Comp i j f g a] -> ShowS #

type Repr k (Comp k * f g) x Source # 
type Repr k (Comp k * f g) x = f (Repr k g x)

comp :: Functor f => (a -> g b) -> f a -> Comp f g b Source #

Wrap a result of fmap