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.Foldable.Constrained

Description

 
Synopsis

Documentation

class Constrained f => CFoldable f where Source #

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

Minimal complete definition

cfoldMap | cfoldr

Methods

cfold :: (Monoid m, Constraints f m) => f m -> m Source #

Combine the elements of a structure using a monoid.

cfoldMap :: (Monoid m, Constraints f a) => (a -> m) -> f a -> m Source #

Map each element of the structure to a monoid, and combine the results.

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

Right-associative fold of a structure.

In the case of lists, cfoldr, when applied to a binary operator, a starting value (typically the right-identity of the operator), and a list, reduces the list using the binary operator, from right to left:

cfoldr f z [x1, x2, ..., xn] == x1 `f` (x2 `f` ... (xn `f` z)...)

Note that, since the head of the resulting expression is produced by an application of the operator to the first element of the list, cfoldr can produce a terminating expression from an infinite list.

For a general CFoldable structure this should be semantically identical to,

cfoldr f z = foldr f z . ctoList

cfoldr' :: Constraints f a => (a -> b -> b) -> b -> f a -> b Source #

Right-associative fold of a structure, but with strict application of the operator.

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

Left-associative fold of a structure.

In the case of lists, cfoldl, when applied to a binary operator, a starting value (typically the left-identity of the operator), and a list, reduces the list using the binary operator, from left to right:

cfoldl f z [x1, x2, ..., xn] == (...((z `f` x1) `f` x2) `f`...) `f` xn

Note that to produce the outermost application of the operator the entire input list must be traversed. This means that cfoldl' will diverge if given an infinite list.

Also note that if you want an efficient left-fold, you probably want to use cfoldl' instead of cfoldl. The reason for this is that latter does not force the "inner" results (e.g. z f x1 in the above example) before applying them to the operator (e.g. to (f x2)). This results in a thunk chain O(n) elements long, which then must be evaluated from the outside-in.

For a general CFoldable structure this should be semantically identical to,

cfoldl f z = foldl f z . ctoList

cfoldl' :: Constraints f a => (b -> a -> b) -> b -> f a -> b Source #

Left-associative fold of a structure but with strict application of the operator.

This ensures that each step of the fold is forced to weak head normal form before being applied, avoiding the collection of thunks that would otherwise occur. This is often what you want to strictly reduce a finite list to a single, monolithic result (e.g. clength).

For a general CFoldable structure this should be semantically identical to,

cfoldl f z = foldl' f z . ctoList

cfoldr1 :: Constraints f a => (a -> a -> a) -> f a -> a Source #

A variant of cfoldr that has no base case, and thus may only be applied to non-empty structures.

cfoldr1 f = foldr1 f . ctoList

cfoldl1 :: Constraints f a => (a -> a -> a) -> f a -> a Source #

A variant of cfoldl that has no base case, and thus may only be applied to non-empty structures.

cfoldl1 f = foldl1 f . ctoList

ctoList :: Constraints f a => f a -> [a] Source #

List of elements of a structure, from left to right.

cnull :: Constraints f a => f a -> Bool Source #

Test whether the structure is empty. The default implementation is optimized for structures that are similar to cons-lists, because there is no general way to do better.

clength :: Constraints f a => f a -> Int Source #

Returns the size/length of a finite structure as an Int. The default implementation is optimized for structures that are similar to cons-lists, because there is no general way to do better.

celem :: (Eq a, Constraints f a) => a -> f a -> Bool Source #

Does the element occur in the structure?

cmaximum :: forall a. (Ord a, Constraints f a) => f a -> a Source #

The largest element of a non-empty structure.

cminimum :: forall a. (Ord a, Constraints f a) => f a -> a Source #

The least element of a non-empty structure.

csum :: (Num a, Constraints f a) => f a -> a Source #

The csum function computes the sum of the numbers of a structure.

cproduct :: (Num a, Constraints f a) => f a -> a Source #

The cproduct function computes the product of the numbers of a structure.

Instances
CFoldable [] Source # 
Instance details

Defined in Data.Foldable.Constrained

Methods

cfold :: (Monoid m, Constraints [] m) => [m] -> m Source #

cfoldMap :: (Monoid m, Constraints [] a) => (a -> m) -> [a] -> m Source #

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

cfoldr' :: Constraints [] a => (a -> b -> b) -> b -> [a] -> b Source #

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

cfoldl' :: Constraints [] a => (b -> a -> b) -> b -> [a] -> b Source #

cfoldr1 :: Constraints [] a => (a -> a -> a) -> [a] -> a Source #

cfoldl1 :: Constraints [] a => (a -> a -> a) -> [a] -> a Source #

ctoList :: Constraints [] a => [a] -> [a] Source #

cnull :: Constraints [] a => [a] -> Bool Source #

clength :: Constraints [] a => [a] -> Int Source #

celem :: (Eq a, Constraints [] a) => a -> [a] -> Bool Source #

cmaximum :: (Ord a, Constraints [] a) => [a] -> a Source #

cminimum :: (Ord a, Constraints [] a) => [a] -> a Source #

csum :: (Num a, Constraints [] a) => [a] -> a Source #

cproduct :: (Num a, Constraints [] a) => [a] -> a Source #

CFoldable Maybe Source # 
Instance details

Defined in Data.Foldable.Constrained

Methods

cfold :: (Monoid m, Constraints Maybe m) => Maybe m -> m Source #

cfoldMap :: (Monoid m, Constraints Maybe a) => (a -> m) -> Maybe a -> m Source #

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

cfoldr' :: Constraints Maybe a => (a -> b -> b) -> b -> Maybe a -> b Source #

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

cfoldl' :: Constraints Maybe a => (b -> a -> b) -> b -> Maybe a -> b Source #

cfoldr1 :: Constraints Maybe a => (a -> a -> a) -> Maybe a -> a Source #

cfoldl1 :: Constraints Maybe a => (a -> a -> a) -> Maybe a -> a Source #

ctoList :: Constraints Maybe a => Maybe a -> [a] Source #

cnull :: Constraints Maybe a => Maybe a -> Bool Source #

clength :: Constraints Maybe a => Maybe a -> Int Source #

celem :: (Eq a, Constraints Maybe a) => a -> Maybe a -> Bool Source #

cmaximum :: (Ord a, Constraints Maybe a) => Maybe a -> a Source #

cminimum :: (Ord a, Constraints Maybe a) => Maybe a -> a Source #

csum :: (Num a, Constraints Maybe a) => Maybe a -> a Source #

cproduct :: (Num a, Constraints Maybe a) => Maybe a -> a Source #

CFoldable Min Source # 
Instance details

Defined in Data.Foldable.Constrained

Methods

cfold :: (Monoid m, Constraints Min m) => Min m -> m Source #

cfoldMap :: (Monoid m, Constraints Min a) => (a -> m) -> Min a -> m Source #

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

cfoldr' :: Constraints Min a => (a -> b -> b) -> b -> Min a -> b Source #

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

cfoldl' :: Constraints Min a => (b -> a -> b) -> b -> Min a -> b Source #

cfoldr1 :: Constraints Min a => (a -> a -> a) -> Min a -> a Source #

cfoldl1 :: Constraints Min a => (a -> a -> a) -> Min a -> a Source #

ctoList :: Constraints Min a => Min a -> [a] Source #

cnull :: Constraints Min a => Min a -> Bool Source #

clength :: Constraints Min a => Min a -> Int Source #

celem :: (Eq a, Constraints Min a) => a -> Min a -> Bool Source #

cmaximum :: (Ord a, Constraints Min a) => Min a -> a Source #

cminimum :: (Ord a, Constraints Min a) => Min a -> a Source #

csum :: (Num a, Constraints Min a) => Min a -> a Source #

cproduct :: (Num a, Constraints Min a) => Min a -> a Source #

CFoldable Max Source # 
Instance details

Defined in Data.Foldable.Constrained

Methods

cfold :: (Monoid m, Constraints Max m) => Max m -> m Source #

cfoldMap :: (Monoid m, Constraints Max a) => (a -> m) -> Max a -> m Source #

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

cfoldr' :: Constraints Max a => (a -> b -> b) -> b -> Max a -> b Source #

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

cfoldl' :: Constraints Max a => (b -> a -> b) -> b -> Max a -> b Source #

cfoldr1 :: Constraints Max a => (a -> a -> a) -> Max a -> a Source #

cfoldl1 :: Constraints Max a => (a -> a -> a) -> Max a -> a Source #

ctoList :: Constraints Max a => Max a -> [a] Source #

cnull :: Constraints Max a => Max a -> Bool Source #

clength :: Constraints Max a => Max a -> Int Source #

celem :: (Eq a, Constraints Max a) => a -> Max a -> Bool Source #

cmaximum :: (Ord a, Constraints Max a) => Max a -> a Source #

cminimum :: (Ord a, Constraints Max a) => Max a -> a Source #

csum :: (Num a, Constraints Max a) => Max a -> a Source #

cproduct :: (Num a, Constraints Max a) => Max a -> a Source #

CFoldable First Source # 
Instance details

Defined in Data.Foldable.Constrained

Methods

cfold :: (Monoid m, Constraints First m) => First m -> m Source #

cfoldMap :: (Monoid m, Constraints First a) => (a -> m) -> First a -> m Source #

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

cfoldr' :: Constraints First a => (a -> b -> b) -> b -> First a -> b Source #

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

cfoldl' :: Constraints First a => (b -> a -> b) -> b -> First a -> b Source #

cfoldr1 :: Constraints First a => (a -> a -> a) -> First a -> a Source #

cfoldl1 :: Constraints First a => (a -> a -> a) -> First a -> a Source #

ctoList :: Constraints First a => First a -> [a] Source #

cnull :: Constraints First a => First a -> Bool Source #

clength :: Constraints First a => First a -> Int Source #

celem :: (Eq a, Constraints First a) => a -> First a -> Bool Source #

cmaximum :: (Ord a, Constraints First a) => First a -> a Source #

cminimum :: (Ord a, Constraints First a) => First a -> a Source #

csum :: (Num a, Constraints First a) => First a -> a Source #

cproduct :: (Num a, Constraints First a) => First a -> a Source #

CFoldable Last Source # 
Instance details

Defined in Data.Foldable.Constrained

Methods

cfold :: (Monoid m, Constraints Last m) => Last m -> m Source #

cfoldMap :: (Monoid m, Constraints Last a) => (a -> m) -> Last a -> m Source #

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

cfoldr' :: Constraints Last a => (a -> b -> b) -> b -> Last a -> b Source #

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

cfoldl' :: Constraints Last a => (b -> a -> b) -> b -> Last a -> b Source #

cfoldr1 :: Constraints Last a => (a -> a -> a) -> Last a -> a Source #

cfoldl1 :: Constraints Last a => (a -> a -> a) -> Last a -> a Source #

ctoList :: Constraints Last a => Last a -> [a] Source #

cnull :: Constraints Last a => Last a -> Bool Source #

clength :: Constraints Last a => Last a -> Int Source #

celem :: (Eq a, Constraints Last a) => a -> Last a -> Bool Source #

cmaximum :: (Ord a, Constraints Last a) => Last a -> a Source #

cminimum :: (Ord a, Constraints Last a) => Last a -> a Source #

csum :: (Num a, Constraints Last a) => Last a -> a Source #

cproduct :: (Num a, Constraints Last a) => Last a -> a Source #

CFoldable ZipList Source # 
Instance details

Defined in Data.Foldable.Constrained

Methods

cfold :: (Monoid m, Constraints ZipList m) => ZipList m -> m Source #

cfoldMap :: (Monoid m, Constraints ZipList a) => (a -> m) -> ZipList a -> m Source #

cfoldr :: Constraints ZipList a => (a -> b -> b) -> b -> ZipList a -> b Source #

cfoldr' :: Constraints ZipList a => (a -> b -> b) -> b -> ZipList a -> b Source #

cfoldl :: Constraints ZipList a => (b -> a -> b) -> b -> ZipList a -> b Source #

cfoldl' :: Constraints ZipList a => (b -> a -> b) -> b -> ZipList a -> b Source #

cfoldr1 :: Constraints ZipList a => (a -> a -> a) -> ZipList a -> a Source #

cfoldl1 :: Constraints ZipList a => (a -> a -> a) -> ZipList a -> a Source #

ctoList :: Constraints ZipList a => ZipList a -> [a] Source #

cnull :: Constraints ZipList a => ZipList a -> Bool Source #

clength :: Constraints ZipList a => ZipList a -> Int Source #

celem :: (Eq a, Constraints ZipList a) => a -> ZipList a -> Bool Source #

cmaximum :: (Ord a, Constraints ZipList a) => ZipList a -> a Source #

cminimum :: (Ord a, Constraints ZipList a) => ZipList a -> a Source #

csum :: (Num a, Constraints ZipList a) => ZipList a -> a Source #

cproduct :: (Num a, Constraints ZipList a) => ZipList a -> a Source #

CFoldable Identity Source # 
Instance details

Defined in Data.Foldable.Constrained

Methods

cfold :: (Monoid m, Constraints Identity m) => Identity m -> m Source #

cfoldMap :: (Monoid m, Constraints Identity a) => (a -> m) -> Identity a -> m Source #

cfoldr :: Constraints Identity a => (a -> b -> b) -> b -> Identity a -> b Source #

cfoldr' :: Constraints Identity a => (a -> b -> b) -> b -> Identity a -> b Source #

cfoldl :: Constraints Identity a => (b -> a -> b) -> b -> Identity a -> b Source #

cfoldl' :: Constraints Identity a => (b -> a -> b) -> b -> Identity a -> b Source #

cfoldr1 :: Constraints Identity a => (a -> a -> a) -> Identity a -> a Source #

cfoldl1 :: Constraints Identity a => (a -> a -> a) -> Identity a -> a Source #

ctoList :: Constraints Identity a => Identity a -> [a] Source #

cnull :: Constraints Identity a => Identity a -> Bool Source #

clength :: Constraints Identity a => Identity a -> Int Source #

celem :: (Eq a, Constraints Identity a) => a -> Identity a -> Bool Source #

cmaximum :: (Ord a, Constraints Identity a) => Identity a -> a Source #

cminimum :: (Ord a, Constraints Identity a) => Identity a -> a Source #

csum :: (Num a, Constraints Identity a) => Identity a -> a Source #

cproduct :: (Num a, Constraints Identity a) => Identity a -> a Source #

CFoldable Dual Source # 
Instance details

Defined in Data.Foldable.Constrained

Methods

cfold :: (Monoid m, Constraints Dual m) => Dual m -> m Source #

cfoldMap :: (Monoid m, Constraints Dual a) => (a -> m) -> Dual a -> m Source #

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

cfoldr' :: Constraints Dual a => (a -> b -> b) -> b -> Dual a -> b Source #

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

cfoldl' :: Constraints Dual a => (b -> a -> b) -> b -> Dual a -> b Source #

cfoldr1 :: Constraints Dual a => (a -> a -> a) -> Dual a -> a Source #

cfoldl1 :: Constraints Dual a => (a -> a -> a) -> Dual a -> a Source #

ctoList :: Constraints Dual a => Dual a -> [a] Source #

cnull :: Constraints Dual a => Dual a -> Bool Source #

clength :: Constraints Dual a => Dual a -> Int Source #

celem :: (Eq a, Constraints Dual a) => a -> Dual a -> Bool Source #

cmaximum :: (Ord a, Constraints Dual a) => Dual a -> a Source #

cminimum :: (Ord a, Constraints Dual a) => Dual a -> a Source #

csum :: (Num a, Constraints Dual a) => Dual a -> a Source #

cproduct :: (Num a, Constraints Dual a) => Dual a -> a Source #

CFoldable Sum Source # 
Instance details

Defined in Data.Foldable.Constrained

Methods

cfold :: (Monoid m, Constraints Sum m) => Sum m -> m Source #

cfoldMap :: (Monoid m, Constraints Sum a) => (a -> m) -> Sum a -> m Source #

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

cfoldr' :: Constraints Sum a => (a -> b -> b) -> b -> Sum a -> b Source #

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

cfoldl' :: Constraints Sum a => (b -> a -> b) -> b -> Sum a -> b Source #

cfoldr1 :: Constraints Sum a => (a -> a -> a) -> Sum a -> a Source #

cfoldl1 :: Constraints Sum a => (a -> a -> a) -> Sum a -> a Source #

ctoList :: Constraints Sum a => Sum a -> [a] Source #

cnull :: Constraints Sum a => Sum a -> Bool Source #

clength :: Constraints Sum a => Sum a -> Int Source #

celem :: (Eq a, Constraints Sum a) => a -> Sum a -> Bool Source #

cmaximum :: (Ord a, Constraints Sum a) => Sum a -> a Source #

cminimum :: (Ord a, Constraints Sum a) => Sum a -> a Source #

csum :: (Num a, Constraints Sum a) => Sum a -> a Source #

cproduct :: (Num a, Constraints Sum a) => Sum a -> a Source #

CFoldable Product Source # 
Instance details

Defined in Data.Foldable.Constrained

Methods

cfold :: (Monoid m, Constraints Product m) => Product m -> m Source #

cfoldMap :: (Monoid m, Constraints Product a) => (a -> m) -> Product a -> m Source #

cfoldr :: Constraints Product a => (a -> b -> b) -> b -> Product a -> b Source #

cfoldr' :: Constraints Product a => (a -> b -> b) -> b -> Product a -> b Source #

cfoldl :: Constraints Product a => (b -> a -> b) -> b -> Product a -> b Source #

cfoldl' :: Constraints Product a => (b -> a -> b) -> b -> Product a -> b Source #

cfoldr1 :: Constraints Product a => (a -> a -> a) -> Product a -> a Source #

cfoldl1 :: Constraints Product a => (a -> a -> a) -> Product a -> a Source #

ctoList :: Constraints Product a => Product a -> [a] Source #

cnull :: Constraints Product a => Product a -> Bool Source #

clength :: Constraints Product a => Product a -> Int Source #

celem :: (Eq a, Constraints Product a) => a -> Product a -> Bool Source #

cmaximum :: (Ord a, Constraints Product a) => Product a -> a Source #

cminimum :: (Ord a, Constraints Product a) => Product a -> a Source #

csum :: (Num a, Constraints Product a) => Product a -> a Source #

cproduct :: (Num a, Constraints Product a) => Product a -> a Source #

CFoldable NonEmpty Source # 
Instance details

Defined in Data.Foldable.Constrained

Methods

cfold :: (Monoid m, Constraints NonEmpty m) => NonEmpty m -> m Source #

cfoldMap :: (Monoid m, Constraints NonEmpty a) => (a -> m) -> NonEmpty a -> m Source #

cfoldr :: Constraints NonEmpty a => (a -> b -> b) -> b -> NonEmpty a -> b Source #

cfoldr' :: Constraints NonEmpty a => (a -> b -> b) -> b -> NonEmpty a -> b Source #

cfoldl :: Constraints NonEmpty a => (b -> a -> b) -> b -> NonEmpty a -> b Source #

cfoldl' :: Constraints NonEmpty a => (b -> a -> b) -> b -> NonEmpty a -> b Source #

cfoldr1 :: Constraints NonEmpty a => (a -> a -> a) -> NonEmpty a -> a Source #

cfoldl1 :: Constraints NonEmpty a => (a -> a -> a) -> NonEmpty a -> a Source #

ctoList :: Constraints NonEmpty a => NonEmpty a -> [a] Source #

cnull :: Constraints NonEmpty a => NonEmpty a -> Bool Source #

clength :: Constraints NonEmpty a => NonEmpty a -> Int Source #

celem :: (Eq a, Constraints NonEmpty a) => a -> NonEmpty a -> Bool Source #

cmaximum :: (Ord a, Constraints NonEmpty a) => NonEmpty a -> a Source #

cminimum :: (Ord a, Constraints NonEmpty a) => NonEmpty a -> a Source #

csum :: (Num a, Constraints NonEmpty a) => NonEmpty a -> a Source #

cproduct :: (Num a, Constraints NonEmpty a) => NonEmpty a -> a Source #

CFoldable (Either a) Source # 
Instance details

Defined in Data.Foldable.Constrained

Methods

cfold :: (Monoid m, Constraints (Either a) m) => Either a m -> m Source #

cfoldMap :: (Monoid m, Constraints (Either a) a0) => (a0 -> m) -> Either a a0 -> m Source #

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

cfoldr' :: Constraints (Either a) a0 => (a0 -> b -> b) -> b -> Either a a0 -> b Source #

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

cfoldl' :: Constraints (Either a) a0 => (b -> a0 -> b) -> b -> Either a a0 -> b Source #

cfoldr1 :: Constraints (Either a) a0 => (a0 -> a0 -> a0) -> Either a a0 -> a0 Source #

cfoldl1 :: Constraints (Either a) a0 => (a0 -> a0 -> a0) -> Either a a0 -> a0 Source #

ctoList :: Constraints (Either a) a0 => Either a a0 -> [a0] Source #

cnull :: Constraints (Either a) a0 => Either a a0 -> Bool Source #

clength :: Constraints (Either a) a0 => Either a a0 -> Int Source #

celem :: (Eq a0, Constraints (Either a) a0) => a0 -> Either a a0 -> Bool Source #

cmaximum :: (Ord a0, Constraints (Either a) a0) => Either a a0 -> a0 Source #

cminimum :: (Ord a0, Constraints (Either a) a0) => Either a a0 -> a0 Source #

csum :: (Num a0, Constraints (Either a) a0) => Either a a0 -> a0 Source #

cproduct :: (Num a0, Constraints (Either a) a0) => Either a a0 -> a0 Source #

CFoldable ((,) a) Source # 
Instance details

Defined in Data.Foldable.Constrained

Methods

cfold :: (Monoid m, Constraints ((,) a) m) => (a, m) -> m Source #

cfoldMap :: (Monoid m, Constraints ((,) a) a0) => (a0 -> m) -> (a, a0) -> m Source #

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

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

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

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

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

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

ctoList :: Constraints ((,) a) a0 => (a, a0) -> [a0] Source #

cnull :: Constraints ((,) a) a0 => (a, a0) -> Bool Source #

clength :: Constraints ((,) a) a0 => (a, a0) -> Int Source #

celem :: (Eq a0, Constraints ((,) a) a0) => a0 -> (a, a0) -> Bool Source #

cmaximum :: (Ord a0, Constraints ((,) a) a0) => (a, a0) -> a0 Source #

cminimum :: (Ord a0, Constraints ((,) a) a0) => (a, a0) -> a0 Source #

csum :: (Num a0, Constraints ((,) a) a0) => (a, a0) -> a0 Source #

cproduct :: (Num a0, Constraints ((,) a) a0) => (a, a0) -> a0 Source #

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

Defined in Data.Foldable.Constrained

Methods

cfold :: (Monoid m, Constraints (Const a) m) => Const a m -> m Source #

cfoldMap :: (Monoid m, Constraints (Const a) a0) => (a0 -> m) -> Const a a0 -> m Source #

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

cfoldr' :: Constraints (Const a) a0 => (a0 -> b -> b) -> b -> Const a a0 -> b Source #

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

cfoldl' :: Constraints (Const a) a0 => (b -> a0 -> b) -> b -> Const a a0 -> b Source #

cfoldr1 :: Constraints (Const a) a0 => (a0 -> a0 -> a0) -> Const a a0 -> a0 Source #

cfoldl1 :: Constraints (Const a) a0 => (a0 -> a0 -> a0) -> Const a a0 -> a0 Source #

ctoList :: Constraints (Const a) a0 => Const a a0 -> [a0] Source #

cnull :: Constraints (Const a) a0 => Const a a0 -> Bool Source #

clength :: Constraints (Const a) a0 => Const a a0 -> Int Source #

celem :: (Eq a0, Constraints (Const a) a0) => a0 -> Const a a0 -> Bool Source #

cmaximum :: (Ord a0, Constraints (Const a) a0) => Const a a0 -> a0 Source #

cminimum :: (Ord a0, Constraints (Const a) a0) => Const a a0 -> a0 Source #

csum :: (Num a0, Constraints (Const a) a0) => Const a a0 -> a0 Source #

cproduct :: (Num a0, Constraints (Const a) a0) => Const a a0 -> a0 Source #

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

Defined in Data.Foldable.Constrained

Methods

cfold :: (Monoid m, Constraints (Ap f) m) => Ap f m -> m Source #

cfoldMap :: (Monoid m, Constraints (Ap f) a) => (a -> m) -> Ap f a -> m Source #

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

cfoldr' :: Constraints (Ap f) a => (a -> b -> b) -> b -> Ap f a -> b Source #

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

cfoldl' :: Constraints (Ap f) a => (b -> a -> b) -> b -> Ap f a -> b Source #

cfoldr1 :: Constraints (Ap f) a => (a -> a -> a) -> Ap f a -> a Source #

cfoldl1 :: Constraints (Ap f) a => (a -> a -> a) -> Ap f a -> a Source #

ctoList :: Constraints (Ap f) a => Ap f a -> [a] Source #

cnull :: Constraints (Ap f) a => Ap f a -> Bool Source #

clength :: Constraints (Ap f) a => Ap f a -> Int Source #

celem :: (Eq a, Constraints (Ap f) a) => a -> Ap f a -> Bool Source #

cmaximum :: (Ord a, Constraints (Ap f) a) => Ap f a -> a Source #

cminimum :: (Ord a, Constraints (Ap f) a) => Ap f a -> a Source #

csum :: (Num a, Constraints (Ap f) a) => Ap f a -> a Source #

cproduct :: (Num a, Constraints (Ap f) a) => Ap f a -> a Source #

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

Defined in Data.Foldable.Constrained

Methods

cfold :: (Monoid m, Constraints (Alt f) m) => Alt f m -> m Source #

cfoldMap :: (Monoid m, Constraints (Alt f) a) => (a -> m) -> Alt f a -> m Source #

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

cfoldr' :: Constraints (Alt f) a => (a -> b -> b) -> b -> Alt f a -> b Source #

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

cfoldl' :: Constraints (Alt f) a => (b -> a -> b) -> b -> Alt f a -> b Source #

cfoldr1 :: Constraints (Alt f) a => (a -> a -> a) -> Alt f a -> a Source #

cfoldl1 :: Constraints (Alt f) a => (a -> a -> a) -> Alt f a -> a Source #

ctoList :: Constraints (Alt f) a => Alt f a -> [a] Source #

cnull :: Constraints (Alt f) a => Alt f a -> Bool Source #

clength :: Constraints (Alt f) a => Alt f a -> Int Source #

celem :: (Eq a, Constraints (Alt f) a) => a -> Alt f a -> Bool Source #

cmaximum :: (Ord a, Constraints (Alt f) a) => Alt f a -> a Source #

cminimum :: (Ord a, Constraints (Alt f) a) => Alt f a -> a Source #

csum :: (Num a, Constraints (Alt f) a) => Alt f a -> a Source #

cproduct :: (Num a, Constraints (Alt f) a) => Alt f a -> a Source #

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

Defined in Data.Foldable.Constrained

Methods

cfold :: (Monoid m, Constraints (Product f g) m) => Product f g m -> m Source #

cfoldMap :: (Monoid m, Constraints (Product f g) a) => (a -> m) -> Product f g a -> m Source #

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

cfoldr' :: Constraints (Product f g) a => (a -> b -> b) -> b -> Product f g a -> b Source #

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

cfoldl' :: Constraints (Product f g) a => (b -> a -> b) -> b -> Product f g a -> b Source #

cfoldr1 :: Constraints (Product f g) a => (a -> a -> a) -> Product f g a -> a Source #

cfoldl1 :: Constraints (Product f g) a => (a -> a -> a) -> Product f g a -> a Source #

ctoList :: Constraints (Product f g) a => Product f g a -> [a] Source #

cnull :: Constraints (Product f g) a => Product f g a -> Bool Source #

clength :: Constraints (Product f g) a => Product f g a -> Int Source #

celem :: (Eq a, Constraints (Product f g) a) => a -> Product f g a -> Bool Source #

cmaximum :: (Ord a, Constraints (Product f g) a) => Product f g a -> a Source #

cminimum :: (Ord a, Constraints (Product f g) a) => Product f g a -> a Source #

csum :: (Num a, Constraints (Product f g) a) => Product f g a -> a Source #

cproduct :: (Num a, Constraints (Product f g) a) => Product f g a -> a Source #

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

Defined in Data.Foldable.Constrained

Methods

cfold :: (Monoid m, Constraints (Sum f g) m) => Sum f g m -> m Source #

cfoldMap :: (Monoid m, Constraints (Sum f g) a) => (a -> m) -> Sum f g a -> m Source #

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

cfoldr' :: Constraints (Sum f g) a => (a -> b -> b) -> b -> Sum f g a -> b Source #

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

cfoldl' :: Constraints (Sum f g) a => (b -> a -> b) -> b -> Sum f g a -> b Source #

cfoldr1 :: Constraints (Sum f g) a => (a -> a -> a) -> Sum f g a -> a Source #

cfoldl1 :: Constraints (Sum f g) a => (a -> a -> a) -> Sum f g a -> a Source #

ctoList :: Constraints (Sum f g) a => Sum f g a -> [a] Source #

cnull :: Constraints (Sum f g) a => Sum f g a -> Bool Source #

clength :: Constraints (Sum f g) a => Sum f g a -> Int Source #

celem :: (Eq a, Constraints (Sum f g) a) => a -> Sum f g a -> Bool Source #

cmaximum :: (Ord a, Constraints (Sum f g) a) => Sum f g a -> a Source #

cminimum :: (Ord a, Constraints (Sum f g) a) => Sum f g a -> a Source #

csum :: (Num a, Constraints (Sum f g) a) => Sum f g a -> a Source #

cproduct :: (Num a, Constraints (Sum f g) a) => Sum f g a -> a Source #

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

Defined in Data.Foldable.Constrained

Methods

cfold :: (Monoid m, Constraints (Compose f g) m) => Compose f g m -> m Source #

cfoldMap :: (Monoid m, Constraints (Compose f g) a) => (a -> m) -> Compose f g a -> m Source #

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

cfoldr' :: Constraints (Compose f g) a => (a -> b -> b) -> b -> Compose f g a -> b Source #

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

cfoldl' :: Constraints (Compose f g) a => (b -> a -> b) -> b -> Compose f g a -> b Source #

cfoldr1 :: Constraints (Compose f g) a => (a -> a -> a) -> Compose f g a -> a Source #

cfoldl1 :: Constraints (Compose f g) a => (a -> a -> a) -> Compose f g a -> a Source #

ctoList :: Constraints (Compose f g) a => Compose f g a -> [a] Source #

cnull :: Constraints (Compose f g) a => Compose f g a -> Bool Source #

clength :: Constraints (Compose f g) a => Compose f g a -> Int Source #

celem :: (Eq a, Constraints (Compose f g) a) => a -> Compose f g a -> Bool Source #

cmaximum :: (Ord a, Constraints (Compose f g) a) => Compose f g a -> a Source #

cminimum :: (Ord a, Constraints (Compose f g) a) => Compose f g a -> a Source #

csum :: (Num a, Constraints (Compose f g) a) => Compose f g a -> a Source #

cproduct :: (Num a, Constraints (Compose f g) a) => Compose f g a -> a Source #

cfoldrM :: (CFoldable f, Monad m, Constraints f a) => (a -> b -> m b) -> b -> f a -> m b Source #

Monadic fold over the elements of a structure, associating to the right, i.e. from right to left.

cfoldlM :: (CFoldable f, Monad m, Constraints f a) => (b -> a -> m b) -> b -> f a -> m b Source #

Monadic fold over the elements of a structure, associating to the left, i.e. from left to right.

ctraverse_ :: (CFoldable f, Applicative f, Constraints f a) => (a -> f b) -> f a -> f () Source #

Map each element of a structure to an action, evaluate these actions from left to right, and ignore the results. For a version that doesn't ignore the results see traverse.

cfor_ :: (CFoldable f, Applicative f, Constraints f a) => f a -> (a -> f b) -> f () Source #

cfor_ is ctraverse_ with its arguments flipped. For a version that doesn't ignore the results see cfor.

>>> for_ [1..4] print
1
2
3
4

cmapM_ :: (CFoldable f, Monad m, Constraints f a) => (a -> m b) -> f a -> m () Source #

Map each element of a structure to a monadic action, evaluate these actions from left to right, and ignore the results. For a version that doesn't ignore the results see mapM.

cforM_ :: (CFoldable f, Monad m, Constraints f a) => f a -> (a -> m b) -> m () Source #

cforM_ is cmapM_ with its arguments flipped. For a version that doesn't ignore the results see forM.

csequenceA_ :: (CFoldable f, Applicative m, Constraints f (m a)) => f (m a) -> m () Source #

Evaluate each action in the structure from left to right, and ignore the results. For a version that doesn't ignore the results see sequenceA.

csequence_ :: (CFoldable f, Monad m, Constraints f a, Constraints f (m a)) => f (m a) -> m () Source #

Evaluate each monadic action in the structure from left to right, and ignore the results. For a version that doesn't ignore the results see sequence.

casum :: (CFoldable f, Alternative m, Constraints f (m a)) => f (m a) -> m a Source #

The sum of a collection of actions, generalizing concat.

asum [Just Hello, Nothing, Just World] Just Hello

cmsum :: (CFoldable f, MonadPlus m, Constraints f (m a)) => f (m a) -> m a Source #

The sum of a collection of actions, generalizing concat.

cconcat :: (CFoldable f, Constraints f [a]) => f [a] -> [a] Source #

The concatenation of all the elements of a container of lists.

cconcatMap :: (CFoldable f, Constraints f a) => (a -> [b]) -> f a -> [b] Source #

Map a function over all the elements of a container and concatenate the resulting lists.

cand :: (CFoldable f, Constraints f Bool) => f Bool -> Bool Source #

cand returns the conjunction of a container of Bools. For the result to be True, the container must be finite; False, however, results from a False value finitely far from the left end.

cor :: (CFoldable f, Constraints f Bool) => f Bool -> Bool Source #

cor returns the disjunction of a container of Bools. For the result to be False, the container must be finite; True, however, results from a True value finitely far from the left end.

cany :: (CFoldable f, Constraints f a) => (a -> Bool) -> f a -> Bool Source #

Determines whether any element of the structure satisfies the predicate.

call :: (CFoldable f, Constraints f a) => (a -> Bool) -> f a -> Bool Source #

Determines whether all elements of the structure satisfy the predicate.

cmaximumBy :: (CFoldable f, Constraints f a) => (a -> a -> Ordering) -> f a -> a Source #

The largest element of a non-empty structure with respect to the given comparison function.

cminimumBy :: (CFoldable f, Constraints f a) => (a -> a -> Ordering) -> f a -> a Source #

The least element of a non-empty structure with respect to the given comparison function.

cnotElem :: (CFoldable f, Eq a, Constraints f a) => a -> f a -> Bool Source #

cnotElem is the negation of celem.

cfind :: (CFoldable f, Constraints f a) => (a -> Bool) -> f a -> Maybe a Source #

The cfind function takes a predicate and a structure and returns the leftmost element of the structure matching the predicate, or Nothing if there is no such element.

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 #