| Portability | non-portable |
|---|---|
| Stability | experimental |
| Maintainer | generics@haskell.org |
Generics.EMGM.Functions.Collect
Description
Summary: Generic function that collects values of a specified type from a generic value.
- newtype Collect f b a = Collect {
- selCollect :: a -> f b
- collect :: (Alternative f, Rep (Collect f b) a) => a -> f b
Documentation
The type of a generic function that takes a value of one type and returns a collection of values of another type.
For datatypes to work with Collect, a special instance must be given. This
instance is trivial to write. Given a type T, the Rep instance looks like
this:
{-# LANGUAGE OverlappingInstances #-}
data T = ...
instance (Alternative f) => Rep (Collect f T) T where
rep = Collect pure
(Note that overlapping instances are required.) This instance triggers when
the result type (the T in Collect f T) matches the value type (the second
T) contained within the argument to collect. See the source of this
module for more examples.
Constructors
| Collect | |
Fields
| |
Instances
| Alternative f => Generic (Collect f b) | |
| Alternative f => Rep (Collect f Char) Char | |
| Alternative f => Rep (Collect f Double) Double | |
| Alternative f => Rep (Collect f Float) Float | |
| Alternative f => Rep (Collect f Integer) Integer | |
| Alternative f => Rep (Collect f Int) Int | |
| Alternative f => Rep (Collect f Bool) Bool | |
| Alternative f => Rep (Collect f ()) () | |
| Alternative f => Rep (Collect f [a]) [a] | |
| Alternative f => Rep (Collect f (Maybe a)) (Maybe a) | |
| Alternative f => Rep (Collect f (Ratio a)) (Ratio a) | |
| Alternative f => Rep (Collect f (Either a b)) (Either a b) | |
| Alternative f => Rep (Collect f (a, b)) (a, b) | |
| Alternative f => Rep (Collect f (a, b, c)) (a, b, c) | |
| Alternative f => Rep (Collect f (a, b, c, d)) (a, b, c, d) | |
| Alternative f => Rep (Collect f (a, b, c, d, e)) (a, b, c, d, e) | |
| Alternative f => Rep (Collect f (a, b, c, d, e, h)) (a, b, c, d, e, h) | |
| Alternative f => Rep (Collect f (a, b, c, d, e, h, i)) (a, b, c, d, e, h, i) |
collect :: (Alternative f, Rep (Collect f b) a) => a -> f bSource
Collect values of type b from some value of type a. An empty means
no values were collected. If you expected otherwise, be sure that you have an
instance such as for the type Rep (Collect B) BB that you are
collecting.
collect works by searching a datatype for values that are the same type as
the return type specified. Here are some examples using the same value with
different return types:
ghci> let x = [Left1,Right'a',Left2] :: [EitherIntChar] ghci> collect x :: [Int] [1,2] ghci> collect x :: [Char] "a" ghci> collect x == xTrue
Note that the numerical constants have been declared Int using the type
annotation. Since these natively have the type , you may need
to give explicit types. By design, there is no connection that can be
inferred between the return type and the argument type.
Num a => a
collect only works if there is an instance for the return type as described
in the newtype .
Collect