emgm-0.3.1: Extensible and Modular Generics for the MassesSource codeContentsIndex
Generics.EMGM.Functions.Collect
Portabilitynon-portable
Stabilityexperimental
Maintainergenerics@haskell.org
Description
Summary: Generic function that collects all values of a specified type from a generic value.
Synopsis
newtype Collect b a = Collect {
selCollect :: a -> [b]
}
collect :: Rep (Collect b) a => a -> [b]
Documentation
newtype Collect b a Source

The type of a generic function that takes a value of one type and returns a list 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 Rep (Collect T) T where
    rep = Collect (:[])

(Note the requirement of overlapping instances.) This instance triggers when the result type (the first T) matches some value type (the second T) contained within the argument to collect. See the source of this module for more examples.

Constructors
Collect
selCollect :: a -> [b]
show/hide Instances
Generic (Collect b)
Rep (Collect Bool) Bool
Rep (Collect Char) Char
Rep (Collect Double) Double
Rep (Collect Float) Float
Rep (Collect Int) Int
Rep (Collect Integer) Integer
Rep (Collect ()) ()
Rep (Collect ([] a)) ([] a)
Rep (Collect (Maybe a)) (Maybe a)
Rep (Collect (Either a b)) (Either a b)
Rep (Collect ((,) a b)) ((,) a b)
Rep (Collect ((,,) a b c)) ((,,) a b c)
Rep (Collect ((,,,) a b c d)) ((,,,) a b c d)
Rep (Collect ((,,,,) a b c d e)) ((,,,,) a b c d e)
Rep (Collect ((,,,,,) a b c d e f)) ((,,,,,) a b c d e f)
Rep (Collect ((,,,,,,) a b c d e f h)) ((,,,,,,) a b c d e f h)
collect :: Rep (Collect b) a => a -> [b]Source

Collect values of type b from some value of type a. An empty list means no values were collected. If you expected otherwise, be sure that you have an instance such as Rep (Collect B) B for the type B 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 = [Left 1, Right 'a', Left 2] :: [Either Int Char]
   ghci> collect x :: [Int]
   [1,2]
   ghci> collect x :: [Char]
   "a"
   ghci> collect x == x
   True

Note that the numerical constants have been declared Int using the type annotation. Since these natively have the type Num a => a, 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.

collect only works if there is an instance for the return type as described in the newtype Collect.

Produced by Haddock version 2.4.2