data-filter-0.1.0.0: Utilities for filtering

Copyright(c) Sophie Hirn 2018
LicenseBSD2
Maintainersophie.hirn@wyvernscale.com
Safe HaskellSafe
LanguageHaskell2010

Data.Filter

Contents

Description

Some helpers to make using Prelude.filter and similar value selection a bit easier. Includes combinators for predicates as well as an operator to match the constructor used for the given value.

Synopsis

Constructors

The (=?=)-operator can be used to check whether two values were generated using the same constructor. For this to work, the underlying data type must instantiate Generic, parameters to the constructor can additionally be left out if their type implements ReduceWith.

constrName :: (HasConstructor (Rep a), Generic a) => a -> String Source #

Retrieve the constructor name of the given value as a string. This implementation is taken from https://stackoverflow.com/questions/48179380/getting-the-data-constructor-name-as-a-string-using-ghc-generics .

class HasConstructor (f :: * -> *) where Source #

Automatically derived from Generic instances.

Minimal complete definition

genericConstrName

Methods

genericConstrName :: f x -> String Source #

Reduction

Constructors can be reduced to values by passing them arbitrary arguments. The actual value of those does not impact the result of the (=?=)-operator. For lazy members, passing undefined works just fine, but putting undefined into strict fields causes carnage. ReduceWith provides arbitrary values, deriving from Default where possible.

class ReduceWith a where Source #

Type that can be reduced away from a constructor. Use this to make your data types compatible. The reduction process and the (=?=)-operator do not evaluate fields, therefore creating an empty instance which defaults to reduceWith = undefined is okay as long as no reduced field of this type is strict.

Methods

reduceWith :: a Source #

class (HasConstructor (Rep c), Generic c) => Reduce a c | a -> c where Source #

Reduction of a constructor a -> ... -> c to a value of type c.

Minimal complete definition

reduce

Methods

reduce :: a -> c Source #

Instances

(HasConstructor (Rep a), Generic a) => Reduce a a Source # 

Methods

reduce :: a -> a Source #

(ReduceWith a, Reduce b c) => Reduce (a -> b) c Source # 

Methods

reduce :: (a -> b) -> c Source #

Operators

(=?=) :: (Reduce a c, Reduce b c) => a -> b -> Bool infixl 4 Source #

Checks whether two values are created by the same data constructor. Also works with constructors that have not yet received all their arguments. This allows for very convenient constructs, e.g.:

>>> Just 1 =?= Just
True
>>> Just 1 =?= Nothing
False
>>> let filterJust = filter (=?= Just)
>>> filterJust [Just 1, Nothing, Just 9001]
[Just 1, Just 9001]
>>> let filterJust_ = mapMaybe $ (=?= Just) ==> fromJust
>>> filterJust_ [Just 1, Nothing, Just 9001]
[1, 9001]
>>> let over9000 = mapMaybe $ ((=?= Just) <&&> (>9000) . fromJust) ==> fromJust
>>> over9000 [Just 1, Nothing, Just 9001]
[9001]

(==>) :: (a -> Bool) -> (a -> b) -> a -> Maybe b Source #

(pred ==> f) x returns Just (f x) if pred x succeeds and Nothing otherwise.

(<||>) :: (a -> Bool) -> (a -> Bool) -> a -> Bool infixl 2 Source #

any_ :: [a -> Bool] -> a -> Bool Source #

(<&&>) :: (a -> Bool) -> (a -> Bool) -> a -> Bool infixl 3 Source #

all_ :: [a -> Bool] -> a -> Bool Source #

Matching Wrappers

data Infinite a Source #

Adds negative and positive infinity to an ordered type. The fromEnum function is inherently susceptible to overflow since the class Enum is defined using Int instead of Integer, but this should not cause trouble with "small" enums.

Constructors

NegInfin 
Exact !a 
PosInfin 

Instances

Functor Infinite Source # 

Methods

fmap :: (a -> b) -> Infinite a -> Infinite b #

(<$) :: a -> Infinite b -> Infinite a #

(Eq a, Bounded a, Enum a) => Enum (Infinite a) Source # 
Eq a => Eq (Infinite a) Source # 

Methods

(==) :: Infinite a -> Infinite a -> Bool #

(/=) :: Infinite a -> Infinite a -> Bool #

Ord a => Ord (Infinite a) Source # 

Methods

compare :: Infinite a -> Infinite a -> Ordering #

(<) :: Infinite a -> Infinite a -> Bool #

(<=) :: Infinite a -> Infinite a -> Bool #

(>) :: Infinite a -> Infinite a -> Bool #

(>=) :: Infinite a -> Infinite a -> Bool #

max :: Infinite a -> Infinite a -> Infinite a #

min :: Infinite a -> Infinite a -> Infinite a #

Read a => Read (Infinite a) Source # 
Show a => Show (Infinite a) Source # 

Methods

showsPrec :: Int -> Infinite a -> ShowS #

show :: Infinite a -> String #

showList :: [Infinite a] -> ShowS #

Generic (Infinite a) Source # 

Associated Types

type Rep (Infinite a) :: * -> * #

Methods

from :: Infinite a -> Rep (Infinite a) x #

to :: Rep (Infinite a) x -> Infinite a #

Default a => Default (Infinite a) Source # 

Methods

def :: Infinite a #

type Rep (Infinite a) Source # 
type Rep (Infinite a) = D1 * (MetaData "Infinite" "Data.Filter" "data-filter-0.1.0.0-Iqq6i9y3g7Q8H3vdgu0TLT" False) ((:+:) * (C1 * (MetaCons "NegInfin" PrefixI False) (U1 *)) ((:+:) * (C1 * (MetaCons "Exact" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 * a))) (C1 * (MetaCons "PosInfin" PrefixI False) (U1 *))))

Useful functions from other modules

mapMaybe :: (a -> Maybe b) -> [a] -> [b] #

The mapMaybe function is a version of map which can throw out elements. In particular, the functional argument returns something of type Maybe b. If this is Nothing, no element is added on to the result list. If it is Just b, then b is included in the result list.

Examples

Using mapMaybe f x is a shortcut for catMaybes $ map f x in most cases:

>>> import Text.Read ( readMaybe )
>>> let readMaybeInt = readMaybe :: String -> Maybe Int
>>> mapMaybe readMaybeInt ["1", "Foo", "3"]
[1,3]
>>> catMaybes $ map readMaybeInt ["1", "Foo", "3"]
[1,3]

If we map the Just constructor, the entire list should be returned:

>>> mapMaybe Just [1,2,3]
[1,2,3]