emgm-0.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.

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 but different return types:

   GHCi> collect [Just 1, Nothing, Just (2 :: Int)] :: [Int]
   [1,2]
   GHCi> collect [Just 1, Nothing, Just (2 :: Int)] :: [Maybe Int]
   [Just 1,Nothing,Just 2]
   GHCi> collect [Just 1, Nothing, Just (2 :: Int)] :: [[Maybe Int]]
   [[Just 1,Nothing,Just 2]]

Note that the number 2 has the type Int. Some arguments (such as numeric constants which have type Num a => a) may need explicit type annotations. By design, there is no connection that can be inferred between the return type and the argument type.

collect only works if the return type has been made an instance of Rep. The library provides instances for all datatypes with included representation.

An instance is trivial to write. Given a type D, the Rep instance looks like this:

  {-# LANGUAGE OverlappingInstances #-}

  data D = ...

  instance Rep (Collect D) D where
    rep = Collect (:[])

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

Synopsis
newtype Collect b a = Collect {
selCollect :: a -> [b]
}
collect :: Rep (Collect b) a => a -> [b]
Documentation
newtype Collect b a Source
Type for collect
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. See the description of this module for details.
Produced by Haddock version 2.4.2