constrained-0.1: Generalization of standard Functor, Foldable, and Traversable classes

Copyright(c) Sergey Vinokurov 2019
LicenseBSD-2 (see LICENSE)
Maintainersergey@debian
Safe HaskellNone
LanguageHaskell2010

Data.Functor.Constrained

Description

 
Synopsis

Documentation

class Constrained f => CFunctor f where Source #

Like Functor but allows elements to have constraints on them. Laws are the same:

cmap id      == id
cmap (f . g) == cmap f . cmap g

Minimal complete definition

Nothing

Methods

cmap :: (Constraints f a, Constraints f b) => (a -> b) -> f a -> f b Source #

cmap_ :: (Constraints f a, Constraints f b) => a -> f b -> f a Source #

cmap :: (Functor f, Constraints f a, Constraints f b) => (a -> b) -> f a -> f b Source #

Instances
CFunctor [] Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

cmap :: (Constraints [] a, Constraints [] b) => (a -> b) -> [a] -> [b] Source #

cmap_ :: (Constraints [] a, Constraints [] b) => a -> [b] -> [a] Source #

CFunctor Maybe Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

cmap :: (Constraints Maybe a, Constraints Maybe b) => (a -> b) -> Maybe a -> Maybe b Source #

cmap_ :: (Constraints Maybe a, Constraints Maybe b) => a -> Maybe b -> Maybe a Source #

CFunctor Min Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

cmap :: (Constraints Min a, Constraints Min b) => (a -> b) -> Min a -> Min b Source #

cmap_ :: (Constraints Min a, Constraints Min b) => a -> Min b -> Min a Source #

CFunctor Max Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

cmap :: (Constraints Max a, Constraints Max b) => (a -> b) -> Max a -> Max b Source #

cmap_ :: (Constraints Max a, Constraints Max b) => a -> Max b -> Max a Source #

CFunctor First Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

cmap :: (Constraints First a, Constraints First b) => (a -> b) -> First a -> First b Source #

cmap_ :: (Constraints First a, Constraints First b) => a -> First b -> First a Source #

CFunctor Last Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

cmap :: (Constraints Last a, Constraints Last b) => (a -> b) -> Last a -> Last b Source #

cmap_ :: (Constraints Last a, Constraints Last b) => a -> Last b -> Last a Source #

CFunctor ZipList Source # 
Instance details

Defined in Data.Functor.Constrained

CFunctor Identity Source # 
Instance details

Defined in Data.Functor.Constrained

CFunctor Dual Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

cmap :: (Constraints Dual a, Constraints Dual b) => (a -> b) -> Dual a -> Dual b Source #

cmap_ :: (Constraints Dual a, Constraints Dual b) => a -> Dual b -> Dual a Source #

CFunctor Sum Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

cmap :: (Constraints Sum a, Constraints Sum b) => (a -> b) -> Sum a -> Sum b Source #

cmap_ :: (Constraints Sum a, Constraints Sum b) => a -> Sum b -> Sum a Source #

CFunctor Product Source # 
Instance details

Defined in Data.Functor.Constrained

CFunctor NonEmpty Source # 
Instance details

Defined in Data.Functor.Constrained

CFunctor (Either a) Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

cmap :: (Constraints (Either a) a0, Constraints (Either a) b) => (a0 -> b) -> Either a a0 -> Either a b Source #

cmap_ :: (Constraints (Either a) a0, Constraints (Either a) b) => a0 -> Either a b -> Either a a0 Source #

CFunctor ((,) a) Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

cmap :: (Constraints ((,) a) a0, Constraints ((,) a) b) => (a0 -> b) -> (a, a0) -> (a, b) Source #

cmap_ :: (Constraints ((,) a) a0, Constraints ((,) a) b) => a0 -> (a, b) -> (a, a0) Source #

CFunctor (Const a :: Type -> Type) Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

cmap :: (Constraints (Const a) a0, Constraints (Const a) b) => (a0 -> b) -> Const a a0 -> Const a b Source #

cmap_ :: (Constraints (Const a) a0, Constraints (Const a) b) => a0 -> Const a b -> Const a a0 Source #

CFunctor f => CFunctor (Ap f) Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

cmap :: (Constraints (Ap f) a, Constraints (Ap f) b) => (a -> b) -> Ap f a -> Ap f b Source #

cmap_ :: (Constraints (Ap f) a, Constraints (Ap f) b) => a -> Ap f b -> Ap f a Source #

CFunctor f => CFunctor (Alt f) Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

cmap :: (Constraints (Alt f) a, Constraints (Alt f) b) => (a -> b) -> Alt f a -> Alt f b Source #

cmap_ :: (Constraints (Alt f) a, Constraints (Alt f) b) => a -> Alt f b -> Alt f a Source #

(CFunctor f, CFunctor g) => CFunctor (Product f g) Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

cmap :: (Constraints (Product f g) a, Constraints (Product f g) b) => (a -> b) -> Product f g a -> Product f g b Source #

cmap_ :: (Constraints (Product f g) a, Constraints (Product f g) b) => a -> Product f g b -> Product f g a Source #

(CFunctor f, CFunctor g) => CFunctor (Sum f g) Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

cmap :: (Constraints (Sum f g) a, Constraints (Sum f g) b) => (a -> b) -> Sum f g a -> Sum f g b Source #

cmap_ :: (Constraints (Sum f g) a, Constraints (Sum f g) b) => a -> Sum f g b -> Sum f g a Source #

(CFunctor f, CFunctor g) => CFunctor (Compose f g) Source # 
Instance details

Defined in Data.Functor.Constrained

Methods

cmap :: (Constraints (Compose f g) a, Constraints (Compose f g) b) => (a -> b) -> Compose f g a -> Compose f g b Source #

cmap_ :: (Constraints (Compose f g) a, Constraints (Compose f g) b) => a -> Compose f g b -> Compose f g a Source #

class NoConstraints (a :: k) Source #

Used to specify values for Constraints type family to indicate absence of any constraints (i.e. empty Constraint).

Instances
NoConstraints (a :: k) Source # 
Instance details

Defined in Data.Constrained

class Constrained (f :: k2 -> k1) Source #

Specification of constrains that a functor might impose on its elements. For example, sets typically require that their elements are ordered and unboxed vectors require elements to have an instance of special class that allows them to be packed in memory.

NB The Constraints type family is associated with a typeclass in order to improve type inference. Whenever a typeclass constraint will be present, instance is guaranteed to exist and typechecker is going to take advantage of that.

Associated Types

type Constraints (f :: k2 -> k1) :: k2 -> Constraint Source #

Instances
Constrained f => Constrained (Alt f :: k2 -> Type) Source # 
Instance details

Defined in Data.Constrained

Associated Types

type Constraints (Alt f) :: k2 -> Constraint Source #

Constrained f => Constrained (Ap f :: k2 -> Type) Source # 
Instance details

Defined in Data.Constrained

Associated Types

type Constraints (Ap f) :: k2 -> Constraint Source #

Constrained (Const a :: k2 -> Type) Source # 
Instance details

Defined in Data.Constrained

Associated Types

type Constraints (Const a) :: k2 -> Constraint Source #

(Constrained f, Constrained g) => Constrained (Sum f g :: k2 -> Type) Source # 
Instance details

Defined in Data.Constrained

Associated Types

type Constraints (Sum f g) :: k2 -> Constraint Source #

(Constrained f, Constrained g) => Constrained (Product f g :: k2 -> Type) Source # 
Instance details

Defined in Data.Constrained

Associated Types

type Constraints (Product f g) :: k2 -> Constraint Source #

(Constrained f, Constrained g) => Constrained (Compose f g :: k2 -> Type) Source # 
Instance details

Defined in Data.Constrained

Associated Types

type Constraints (Compose f g) :: k2 -> Constraint Source #

Constrained [] Source # 
Instance details

Defined in Data.Constrained

Associated Types

type Constraints [] :: k2 -> Constraint Source #

Constrained Maybe Source # 
Instance details

Defined in Data.Constrained

Associated Types

type Constraints Maybe :: k2 -> Constraint Source #

Constrained Min Source # 
Instance details

Defined in Data.Constrained

Associated Types

type Constraints Min :: k2 -> Constraint Source #

Constrained Max Source # 
Instance details

Defined in Data.Constrained

Associated Types

type Constraints Max :: k2 -> Constraint Source #

Constrained First Source # 
Instance details

Defined in Data.Constrained

Associated Types

type Constraints First :: k2 -> Constraint Source #

Constrained Last Source # 
Instance details

Defined in Data.Constrained

Associated Types

type Constraints Last :: k2 -> Constraint Source #

Constrained ZipList Source # 
Instance details

Defined in Data.Constrained

Associated Types

type Constraints ZipList :: k2 -> Constraint Source #

Constrained Identity Source # 
Instance details

Defined in Data.Constrained

Associated Types

type Constraints Identity :: k2 -> Constraint Source #

Constrained Dual Source # 
Instance details

Defined in Data.Constrained

Associated Types

type Constraints Dual :: k2 -> Constraint Source #

Constrained Sum Source # 
Instance details

Defined in Data.Constrained

Associated Types

type Constraints Sum :: k2 -> Constraint Source #

Constrained Product Source # 
Instance details

Defined in Data.Constrained

Associated Types

type Constraints Product :: k2 -> Constraint Source #

Constrained NonEmpty Source # 
Instance details

Defined in Data.Constrained

Associated Types

type Constraints NonEmpty :: k2 -> Constraint Source #

Constrained (Either a :: Type -> Type) Source # 
Instance details

Defined in Data.Constrained

Associated Types

type Constraints (Either a) :: k2 -> Constraint Source #

Constrained ((,) a :: Type -> Type) Source # 
Instance details

Defined in Data.Constrained

Associated Types

type Constraints ((,) a) :: k2 -> Constraint Source #