Safe Haskell | Safe |
---|---|
Language | Haskell2010 |
Data.Easy
Description
easy-data
aims to make
, Either
, List
, Tuple
and
Monoid
counterparts to the functions originally defined in
Data.Maybe, whenever applicable.Bool
This module also adds some extra useful functions, that can be found in otherwise disperse packages, pages, mailing lists, etc. A relevant link will be included whenever appropriate, or just a simple note regarding where to find the other implementations. The main goal is to have a consistent set of sensible convertions between types, providing either default values or custom error messages when faced with partial functions (in a mathematical sense).
This module is undoubtably neither original, nor providing the 'best' implementations. Its goal is instead to provide a regular and consistent set of functions, easy do memorize and use, for the Haskell beginner.
Most functions are one-liners, and you should read their actual code, to either use it as a more idiomatic haskell code, or to develop a better version yourself. Most of these functions are hand-picked from one of the following libraries, that also feature a lot of other goodies, so you should check them out.
safe
: http://hackage.haskell.org/package/safe
either
: http://hackage.haskell.org/package/either
errors
: http://hackage.haskell.org/package/errors
basic-prelude
:http://hackage.haskell.org/package/basic-prelude
missingh
: http://hackage.haskell.org/package/MissingH
utility-ht
: http://hackage.haskell.org/package/utility-ht
Note that the Safe module is re-exported by this module. Please notify me if you think I'm missing some other library.
For monad related functions, check my other related module,
Control.Monad.Trans.Convert, or the modules that inspired it, either
and
errors
.
Some choices have been made, and I am open to discussion whether they are adequate or not. Please contribute and help me make this a (even) more easy and consistent module.
- module Safe
- maybeToMonoid :: Monoid a => Maybe a -> a
- monoidToMaybe :: (Eq a, Monoid a) => a -> Maybe a
- fromLeft :: a -> Either a b -> a
- fromRight :: b -> Either a b -> b
- fromLeft' :: Either a b -> a
- fromRight' :: Either a b -> b
- mapBoth :: (a -> c) -> (b -> d) -> Either a b -> Either c d
- mapLeft :: (a -> c) -> Either a b -> Either c b
- mapRight :: (b -> c) -> Either a b -> Either a c
- whenLeft :: Applicative m => Either a b -> (a -> m ()) -> m ()
- whenRight :: Applicative m => Either a b -> (b -> m ()) -> m ()
- unlessLeft :: Applicative m => Either a b -> (b -> m ()) -> m ()
- unlessRight :: Applicative m => Either a b -> (a -> m ()) -> m ()
- leftToMaybe :: Either a b -> Maybe a
- rightToMaybe :: Either a b -> Maybe b
- fromRightNote :: String -> Either a b -> b
- fromLeftNote :: String -> Either a b -> a
- fromEither :: b -> Either a b -> b
- listToEither :: a -> [b] -> Either a b
- eitherToList :: Either a b -> [b]
- catEithers :: [Either a b] -> [b]
- mapEither :: (a -> Either b c) -> [a] -> [c]
- maybeToEither :: a -> Maybe b -> Either a b
- eitherToMaybe :: Either a b -> Maybe b
- eitherToMonoid :: Monoid b => Either a b -> b
- monoidToEither :: (Eq b, Monoid b) => a -> b -> Either a b
- joinEitherMonoid :: (Eq b, Monoid b) => a -> Either a b -> Either a b
- list :: b -> ([a] -> b) -> [a] -> b
- isFilled :: [a] -> Bool
- notNull :: [a] -> Bool
- isNull :: [a] -> Bool
- fromHeadNote :: String -> [a] -> a
- fromList :: a -> [a] -> a
- catLists :: Eq a => [[a]] -> [[a]]
- mapList :: (a -> [b]) -> [a] -> [b]
- singleton :: a -> [a]
- mapV :: a -> [a -> b] -> [b]
- nubSort :: Ord a => [a] -> [a]
- nubSort' :: (Ord a, Monoid a) => [a] -> [a]
- atLeast :: Int -> [a] -> Bool
- pair :: Monoid c => (a -> c) -> (b -> c) -> (a, b) -> c
- pairS :: Monoid b => (a -> b) -> (a, a) -> b
- isPairNotEmpty :: (Eq a, Monoid a, Eq b, Monoid b) => (a, b) -> Bool
- isPairEmpty :: (Eq a, Monoid a, Eq b, Monoid b) => (a, b) -> Bool
- fromFst :: (a, b) -> a
- fromSnd :: (a, b) -> b
- fromPairNote :: (Eq a, Monoid a) => String -> (a, a) -> a
- fromPair :: (Eq a, Monoid a) => a -> (a, a) -> a
- listToPairNote :: String -> [a] -> (a, a)
- listToPairs :: [a] -> ([(a, a)], [a])
- group2 :: [a] -> [(a, a)]
- pairToList :: (a, a) -> [a]
- catPairs :: (Eq a, Monoid a) => [(a, a)] -> [a]
- mapPair :: (Eq b, Monoid b) => (a -> (b, b)) -> [a] -> [b]
- pairToEither :: (Eq b, Monoid b) => (a, b) -> Either a b
- pairToEither' :: (Eq a, Monoid a) => (a, b) -> Either b a
- pairBothToEither :: (Eq a, Monoid a) => b -> (a, a) -> Either b a
- eitherToPair :: Monoid b => a -> Either a b -> (a, b)
- eitherToPair' :: Monoid a => b -> Either b a -> (a, b)
- pairToMaybe :: (Eq a, Monoid a) => (a, a) -> Maybe a
- pairToMaybe' :: (Eq a, Monoid a) => (a, a) -> Maybe a
- pairFstToMaybe :: (Eq a, Monoid a) => (a, b) -> Maybe a
- pairSndToMaybe :: (Eq b, Monoid b) => (a, b) -> Maybe b
- maybeToPair :: Monoid b => a -> Maybe b -> (a, b)
- maybeToPair' :: Monoid a => b -> Maybe a -> (a, b)
- pairToMonoid :: (Eq a, Monoid a) => (a, a) -> a
- pairToMonoid' :: (Eq a, Monoid a) => (a, a) -> a
- triple :: Monoid d => (a -> d) -> (b -> d) -> (c -> d) -> (a, b, c) -> d
- tripleS :: Monoid b => (a -> b) -> (a, a, a) -> b
- isTripleNotEmpty :: (Eq a, Monoid a, Eq b, Monoid b, Eq c, Monoid c) => (a, b, c) -> Bool
- isTripleEmpty :: (Eq a, Monoid a, Eq b, Monoid b, Eq c, Monoid c) => (a, b, c) -> Bool
- fromFst' :: (a, b, c) -> a
- fst' :: (a, b, c) -> a
- fromSnd' :: (a, b, c) -> b
- snd' :: (a, b, c) -> b
- fromTrd' :: (a, b, c) -> c
- trd' :: (a, b, c) -> c
- fromTripleNote :: (Eq a, Monoid a) => String -> (a, a, a) -> a
- fromTriple :: (Eq a, Monoid a) => a -> (a, a, a) -> a
- listToTripleNote :: String -> [a] -> (a, a, a)
- listToTriples :: [a] -> ([(a, a, a)], [a])
- group3 :: [a] -> [(a, a, a)]
- tripleToList :: (a, a, a) -> [a]
- catTriples :: (Eq a, Monoid a) => [(a, a, a)] -> [a]
- mapTriple :: (Eq b, Monoid b) => (a -> (b, b, b)) -> [a] -> [b]
- toFstPairToTriple :: a -> (b, c) -> (a, b, c)
- toSndPairToTriple :: b -> (a, c) -> (a, b, c)
- toTrdPairToTriple :: c -> (a, b) -> (a, b, c)
- pairToTriple :: c -> (a, b) -> (a, b, c)
- dropFstTripleToPair :: (a, b, c) -> (b, c)
- dropSndTripleToPair :: (a, b, c) -> (a, c)
- dropTrdTripleToPair :: (a, b, c) -> (a, b)
- tripleToPair :: (a, b, c) -> (a, b)
- tripleToMaybe :: (Eq a, Monoid a) => (a, a, a) -> Maybe a
- tripleToMaybe' :: (Eq a, Monoid a) => (a, a, a) -> Maybe a
- tripleToMonoid :: (Eq a, Monoid a) => (a, a, a) -> a
- tripleToMonoid' :: (Eq a, Monoid a) => (a, a, a) -> a
- curry3 :: ((a, b, c) -> d) -> a -> b -> c -> d
- uncurry3 :: (a -> b -> c -> d) -> (a, b, c) -> d
- monoid :: (Monoid a, Eq a) => b -> (a -> b) -> a -> b
- isNotEmpty :: (Monoid a, Eq a) => a -> Bool
- notEmpty :: (Monoid a, Eq a) => a -> Bool
- isEmpty :: (Monoid a, Eq a) => a -> Bool
- fromNotEmptyNote :: (Eq a, Monoid a) => String -> a -> a
- fromMonoid :: (Eq a, Monoid a) => a -> a -> a
- (?+) :: (Eq a, Monoid a) => a -> a -> a
- (<!>) :: (Eq a, Monoid a) => a -> a -> a
- listToMonoid :: Monoid a => [a] -> a
- monoidToList :: (Eq a, Monoid a) => a -> [a]
- catMonoids :: (Eq a, Monoid a) => [a] -> [a]
- nonEmpty :: (Eq a, Monoid a) => [a] -> [a]
- mapMonoid :: (Eq b, Monoid b) => (a -> b) -> [a] -> [b]
- getFirst' :: (Eq a, Monoid a) => [a] -> a
- getLast' :: (Eq a, Monoid a) => [a] -> a
- headF :: (Foldable t, Monoid a) => t a -> a
- lastF :: (Foldable t, Monoid a) => t a -> a
- atF :: (Foldable t, Monoid a) => t a -> Int -> a
- (@@) :: (Foldable t, Monoid a) => t a -> Int -> a
- fromBool :: a -> Bool -> a -> a
- fromBoolC :: a -> (a -> Bool) -> a -> a
- catBools :: [Bool] -> [Bool]
- (?) :: Bool -> a -> a -> a
- (?$) :: (a -> Bool) -> a -> a -> a
- (?|) :: a -> (a -> Bool) -> a -> a
- boolToMaybe :: a -> Bool -> Maybe a
- ifToMaybe :: Bool -> a -> Maybe a
- boolCToMaybe :: a -> (a -> Bool) -> Maybe a
- ifCToMaybe :: (a -> Bool) -> a -> Maybe a
- boolToEither :: a -> b -> Bool -> Either a b
- boolCToEither :: a -> b -> (b -> Bool) -> Either a b
- boolToList :: a -> Bool -> [a]
- boolCToList :: a -> (a -> Bool) -> [a]
- boolToMonoid :: Monoid a => a -> Bool -> a
- boolCToMonoid :: Monoid a => a -> (a -> Bool) -> a
- (?&&) :: Monoid a => a -> Bool -> a
- (?&&\) :: Monoid a => a -> (a -> Bool) -> a
- allCond :: a -> [a -> Bool] -> Bool
- anyCond :: a -> [a -> Bool] -> Bool
Module exports
module Safe
Additional functions
Maybe
Since this module maps the Data.Maybe functions to other data types, we mainly just import (and re-export) this module. The extra functions are dedicated to conversions to other types.
maybeToMonoid :: Monoid a => Maybe a -> a Source #
Maybe to monoid conversion
monoidToMaybe :: (Eq a, Monoid a) => a -> Maybe a Source #
Convert a monoid value into a maybe value (Nothing if mempty).
monoidToMaybe = monoid Nothing Just
Either
Copied most of the functions from Data.Either.Combinators, from the "either" package. This package has a huge import list, unnecessary for such simple combinators.
fromRight' :: Either a b -> b Source #
Extracts the element out of a Right
and
throws an error if its argument take the form
.Left
_
Using Control.Lens
:
fromRight'
x ≡ x^?!_Right
>>>
fromRight' (Right 12)
12
mapBoth :: (a -> c) -> (b -> d) -> Either a b -> Either c d Source #
The mapBoth
function takes two functions and applies the first if iff the value
takes the form
and the second if the value takes the form Left
_
.Right
_
Using Data.Bifunctor
:
mapBoth
= bimap
Using Control.Arrow
:
mapBoth
= (+++
)
>>>
mapBoth (*2) (*3) (Left 4)
Left 8
>>>
mapBoth (*2) (*3) (Right 4)
Right 12
mapLeft :: (a -> c) -> Either a b -> Either c b Source #
The mapLeft
function takes a function and applies it to an Either value
iff the value takes the form
.Left
_
Using Data.Bifunctor
:
mapLeft
= first
Using Control.Arrow
:
mapLeft
= (left
)
Using Control.Lens
:
mapLeft
= over _Left
>>>
mapLeft (*2) (Left 4)
Left 8
>>>
mapLeft (*2) (Right "hello")
Right "hello"
mapRight :: (b -> c) -> Either a b -> Either a c Source #
The mapRight
function takes a function and applies it to an Either value
iff the value takes the form
.Right
_
Using Data.Bifunctor
:
mapRight
= second
Using Control.Arrow
:
mapRight
= (right
)
Using Control.Lens
:
mapRight
= over _Right
>>>
mapRight (*2) (Left "hello")
Left "hello"
>>>
mapRight (*2) (Right 4)
Right 8
whenLeft :: Applicative m => Either a b -> (a -> m ()) -> m () Source #
whenRight :: Applicative m => Either a b -> (b -> m ()) -> m () Source #
The whenRight
function takes an Either
value and a function which returns a monad.
The monad is only executed when the given argument takes the form
, otherwise
it does nothing.Right
_
Using Data.Foldable
:
whenRight
≡forM_
Using Control.Lens
:
whenRight
≡ forOf_ _Right
>>>
whenRight (Right 12) print
12
unlessLeft :: Applicative m => Either a b -> (b -> m ()) -> m () Source #
A synonym of whenRight
.
unlessRight :: Applicative m => Either a b -> (a -> m ()) -> m () Source #
A synonym of whenLeft
.
leftToMaybe :: Either a b -> Maybe a Source #
Maybe get the Left
side of an Either
.
leftToMaybe
≡either
Just
(const
Nothing
)
Using Control.Lens
:
leftToMaybe
≡ preview _LeftleftToMaybe
x ≡ x^?_Left
>>>
leftToMaybe (Left 12)
Just 12
>>>
leftToMaybe (Right 12)
Nothing
rightToMaybe :: Either a b -> Maybe b Source #
Maybe get the Right
side of an Either
.
rightToMaybe
≡either
(const
Nothing
)Just
Using Control.Lens
:
rightToMaybe
≡ preview _RightrightToMaybe
x ≡ x^?_Right
>>>
rightToMaybe (Left 12)
Nothing
>>>
rightToMaybe (Right 12)
Just 12
fromRightNote :: String -> Either a b -> b Source #
Force a right value, or otherwise fail with provided error message
fromRightNote err = either (error err) id
fromLeftNote :: String -> Either a b -> a Source #
Force a left value, or otherwise fail with provided error message
fromLeftNote err = either id (error err)
fromEither :: b -> Either a b -> b Source #
Force a right value, providing a default value if the Either is Left
listToEither :: a -> [b] -> Either a b Source #
Extract the first element of a list as a Right value, or else use the default value provided as a Left value
eitherToList :: Either a b -> [b] Source #
Extracts the right value of an either to a singleton list, or an empty list if the Either value is a Left
Note: A Left value is lost in the convertion.
catEithers :: [Either a b] -> [b] Source #
The catEithers
function takes a list of Either
s and returns
a list of all the Right
values.
This is just an alias for rights
, defined in Data.Either
catEithers
=rights
mapEither :: (a -> Either b c) -> [a] -> [c] Source #
The mapEither
function is a version of map
which can throw
out elements. In particular, the functional argument returns
something of type
. If this is 'Left a', no element
is added on to the result list. If it just Either
a b
, then Right
bb
is
included in the result list.
mapEither f = rights . map f
maybeToEither :: a -> Maybe b -> Either a b Source #
Convert a Maybe value to an Either value, with the provided default used as Left value if the Maybe value is Nothing
eitherToMaybe :: Either a b -> Maybe b Source #
Convert an Either value to a Maybe value
This function is provided with a different name convention on
Data.Either.Combinators
:
eitherToMaybe
=rightToMaybe
eitherToMonoid :: Monoid b => Either a b -> b Source #
eitherToMonoid extract the right sided monoid into a single monoid value, or mempty in the case of a left value.
eitherToMonoid = either mempty id
monoidToEither :: (Eq b, Monoid b) => a -> b -> Either a b Source #
monoidToEither extracts a non-empty value to the right side, or
otherwise fills the Left
side with the provided value.
joinEitherMonoid :: (Eq b, Monoid b) => a -> Either a b -> Either a b Source #
Case analysis for a either monoid. If the right side of the monoid
is
, then the value is transformed to a left value, using
the provided function.mempty
List
Data.Maybe counterparts for List, plus some extra functions.
One special note for nubSort
: this is the only 'optimized'
function in this library, mainly because the original
nub . sort
performance is so bad.
Nevertheless, never forget that you should probably not be using
lists anyhow:
http://www.haskell.org/haskellwiki/Performance
list :: b -> ([a] -> b) -> [a] -> b Source #
Apply a function to a non-empty list, and retrieve its result or the default provided value if the list is empty.
fromHeadNote :: String -> [a] -> a Source #
fromList :: a -> [a] -> a Source #
Returns the first value of a list if not empty, or the provided default value if the list is empty
singleton :: a -> [a] Source #
Insert a single value into a list
singleton = return
or
singleton = (:[])
mapV :: a -> [a -> b] -> [b] Source #
map a value over a list of functions, and return a list of values
See: http://www.haskell.org/pipermail/haskell-cafe/2007-February/022694.html
Alternative 1: mapV value = map ($ value)
Alternative 2: mapV value lst = sequence lst value
nubSort :: Ord a => [a] -> [a] Source #
Sort and nub (remove duplicates) from a list.
Specially for large lists, this is much more efficient than nub . sort
.
Note: You shold probably be using Data.Set.
nubSort = Set.toAscList . Set.fromList
nubSort' :: (Ord a, Monoid a) => [a] -> [a] Source #
Sort, nub (remove duplicates) and remove initial empty value, if it
exists. See nubSort
.
atLeast :: Int -> [a] -> Bool Source #
Lazy length: determine if a list has a given size without computing all of its elements.
See http://www.haskell.org/haskellwiki/Haskell_programming_tips
Tuple Pairs
Monoid class restriction will be used in tuple elements whenever necessary to create the concept of 'valid' value.
Here we adopt the convention of a direct
mapping between
and
a tuple pair, meaning that the second value of the pair is considered the
'main' one, whenever applicable. However, if you prefer the first value
to be considered instead, you can use the reciprocal "function'",
like for example Either
pairToMaybe'
.
Note: if you need real heterogeneous lists, see the HList package. http://hackage.haskell.org/package/HList
pair :: Monoid c => (a -> c) -> (b -> c) -> (a, b) -> c Source #
Case evaluation for a tuple pair, reducing
it to a single value
pairS :: Monoid b => (a -> b) -> (a, a) -> b Source #
Case evaluation for single type tuple pairs, simplification of pair
.
isPairNotEmpty :: (Eq a, Monoid a, Eq b, Monoid b) => (a, b) -> Bool Source #
Is the pair tuple 'valid', i.e., does it have at least one non-empty (monoid) value?
isPairEmpty :: (Eq a, Monoid a, Eq b, Monoid b) => (a, b) -> Bool Source #
Is the pair tuple 'invalid', i.e., are both (monoid) elements
mempty
?
fromPairNote :: (Eq a, Monoid a) => String -> (a, a) -> a Source #
mappend
the two monoid elements of a pair
listToPairNote :: String -> [a] -> (a, a) Source #
listToPair grabs the two first elements of a list, and inserts them into a tuple. If not enough elements are available, raise the provided error.
listToPairs :: [a] -> ([(a, a)], [a]) Source #
Groups the elements of a list two by two, also returning the (possible) unpaired item not grouped.
group2 :: [a] -> [(a, a)] Source #
Similar to listToPairs
, but discards the (possible) unpaired item.
pairToList :: (a, a) -> [a] Source #
Convert a single type pair into a two elements list
mapPair :: (Eq b, Monoid b) => (a -> (b, b)) -> [a] -> [b] Source #
Applies a pair returning function to each list element, and keeps only the non-empty mappend results (between the pair elements).
pairToEither' :: (Eq a, Monoid a) => (a, b) -> Either b a Source #
Transform a pair into an either.
The same as pairToEither
, but the first tuple element is considered.
pairBothToEither :: (Eq a, Monoid a) => b -> (a, a) -> Either b a Source #
Transform a pair into an either. Both values are checked for a valid monoid (non-empty). The first to be found is returned as a Right value. If none is found, a default value is returned.
eitherToPair :: Monoid b => a -> Either a b -> (a, b) Source #
eitherToPair' :: Monoid a => b -> Either b a -> (a, b) Source #
pairToMaybe :: (Eq a, Monoid a) => (a, a) -> Maybe a Source #
Transform a pair onto a
This function follows the same convention as Maybe
, and thus
the second value is considered the most important one, and as such
will take precedence over the first if both are not empty.
If you prefer the first value to take precedence, see pairToEither
.
If both elements of the pair are pairToMaybe'
, this function returns mempty
.Nothing
Note: the reciprocal of this function is
.pairToMaybe
pairToMaybe = monoid (monoid Nothing Just a) Just b
pairToMaybe' :: (Eq a, Monoid a) => (a, a) -> Maybe a Source #
Transform a pair onto a
If both the values are non-empty, the first one is returned wrapped in
a Just. If just one value is not-empty, that value is returned,
irrespectively if it is the first or second.
Otherwise, this function returns Nothing.Maybe
Note: the reciprocal of this function is
.pairToMaybe
pairToMaybe' = monoid (monoid Nothing Just b) Just a
pairFstToMaybe :: (Eq a, Monoid a) => (a, b) -> Maybe a Source #
Transform the first element of a pair (if it is a monoid) into an
.
Reciprocal to Maybe
.pairSndToMaybe
pairToMaybe' = monoitToMaybe . fst
pairSndToMaybe :: (Eq b, Monoid b) => (a, b) -> Maybe b Source #
Transform the second element of a pair (if it is a monoid) into a
.
Reciprocal to Maybe
.pairFstToMaybe
pairToMaybe = monoitToMaybe . snd
maybeToPair :: Monoid b => a -> Maybe b -> (a, b) Source #
Transform a
value into a pair. This follows the same
convention as Maybe
, and thus transforms a pairToMaybe
into a Nothing
(def,
, and a mempty
)
into a Just
value(def, value)
.
maybeToPair' :: Monoid a => b -> Maybe a -> (a, b) Source #
Transform a
value into a pair. This follows the same
convention as Maybe
, and thus transforms a pairToMaybe'
into a Nothing
(
, and a mempty
, def)
into a Just
value(value,def)
.
pairToMonoid :: (Eq a, Monoid a) => (a, a) -> a Source #
Finds the first non-empty monoid in a pair, and returns it.
If none found, returns
.mempty
Note: reciprocal to pairToMonoid'
pairToMonoid' :: (Eq a, Monoid a) => (a, a) -> a Source #
Finds the last non-empty monoid in a pair, and returns it.
If none found, returns
.mempty
Tuple Triples
Monoid class restriction will be used in tuple elements whenever necessary to create the concept of 'valid' value.
Since it does not make sense to map a triple to an Either, here we follow a different convention than from pairs, meaning that the first value is always considered the 'valid' value, if the function needs to choose (the first 'valid' value).
Note: if you need real heterogeneous lists, see the HList package. http://hackage.haskell.org/package/HList
Note: we use the postfix ' to distinguish from tuple pairs, for
example in the
function. This clearly doesn't scale to bigger tuples.
If you need those, you probably should be using a better
library than this, no? See http://hackage.haskell.org/package/lens.snd'
triple :: Monoid d => (a -> d) -> (b -> d) -> (c -> d) -> (a, b, c) -> d Source #
Case evaluation for a tuple triple, reducing
it to a single value
tripleS :: Monoid b => (a -> b) -> (a, a, a) -> b Source #
Case evaluation for single type tuple triples, simplification of triple
.
isTripleNotEmpty :: (Eq a, Monoid a, Eq b, Monoid b, Eq c, Monoid c) => (a, b, c) -> Bool Source #
Is the triple tuple 'valid', i.e., does it have at least one non-empty (monoid) value?
isTripleEmpty :: (Eq a, Monoid a, Eq b, Monoid b, Eq c, Monoid c) => (a, b, c) -> Bool Source #
Is the pair tuple 'invalid', i.e., are both (monoid) elements
mempty
?
fromTripleNote :: (Eq a, Monoid a) => String -> (a, a, a) -> a Source #
mappend
the two monoid elements of a pair
fromTriple :: (Eq a, Monoid a) => a -> (a, a, a) -> a Source #
mappend
the three monoid elements of a triple
listToTripleNote :: String -> [a] -> (a, a, a) Source #
listToTriple grabs the two three elements of a list, and inserts them into a triple tuple. If not enough elements are available, raise the provided error.
listToTriples :: [a] -> ([(a, a, a)], [a]) Source #
Groups the elements of a list three by three, also returning the (possible) remaining item(s) (not grouped).
group3 :: [a] -> [(a, a, a)] Source #
Similar to listToTriples
, but discards the (possible) remaining item(s).
tripleToList :: (a, a, a) -> [a] Source #
Convert a single type triple tuple into a three elements list
catTriples :: (Eq a, Monoid a) => [(a, a, a)] -> [a] Source #
mapTriple :: (Eq b, Monoid b) => (a -> (b, b, b)) -> [a] -> [b] Source #
Apply the provided function to each list element resulting in a triple, and keep only the non-empty monoids concat results.
toFstPairToTriple :: a -> (b, c) -> (a, b, c) Source #
Pair to Triple, inserting the missing element in first place
toFstPairToTriple x (y,z) = (x,y,z)
toSndPairToTriple :: b -> (a, c) -> (a, b, c) Source #
Pair to Triple, inserting the missing element in second place
toSndPairToTriple y (x, z) = (x, y, z)
toTrdPairToTriple :: c -> (a, b) -> (a, b, c) Source #
Pair to Triple, inserting the missing element in third place
toTrdPairToTriple z (x, y) = (x, y, z)
pairToTriple :: c -> (a, b) -> (a, b, c) Source #
Alias for toTrdPairToTriple
dropFstTripleToPair :: (a, b, c) -> (b, c) Source #
Triple to pair, removing the first element.
\(_,y,z) -> (y,z)
dropSndTripleToPair :: (a, b, c) -> (a, c) Source #
Triple to pair, removing the second element.
\(x,_,z) -> (x,z)
dropTrdTripleToPair :: (a, b, c) -> (a, b) Source #
Triple to pair, removing the third element.
\(x,y,_) -> (x,y)
tripleToPair :: (a, b, c) -> (a, b) Source #
Alias for dropTrdTripleToPair
.
tripleToMaybe :: (Eq a, Monoid a) => (a, a, a) -> Maybe a Source #
Triple to Maybe. Analogous to
, it keeps the first
non-empty monoid value.pairToMaybe
tripleToMaybe' :: (Eq a, Monoid a) => (a, a, a) -> Maybe a Source #
Triple to Maybe. Analogous to
, it keeps the last
non-empty monoid value.pairToMaybe'
tripleToMonoid :: (Eq a, Monoid a) => (a, a, a) -> a Source #
Triple to Monoid. Analogous to
, it keeps the first
non-empty monoid value.pairToMonoid
tripleToMonoid' :: (Eq a, Monoid a) => (a, a, a) -> a Source #
Triple to Maybe. Analogous to
, it keeps the last
non-empty monoid value.pairToMonoid'
Monoid
The monoid version of the functions deviate slightly from the others, in the sense no value is extracted from or promoted to a monoid. Instead, the value is just checked against mempty, and kept|discarded|operated on accordingly. See http://hackage.haskell.org/package/monoid-subclasses module on hackage for a perhaps saner approach.
monoid :: (Monoid a, Eq a) => b -> (a -> b) -> a -> b Source #
Apply a function to a non-empty monoid, and retrieve its result or the default provided value if the monoid is mempty.
fromNotEmptyNote :: (Eq a, Monoid a) => String -> a -> a Source #
fromNotEmptyNote keeps the monoid value if it is not empty, otherwise it raises an error with the provided message.
Note: This differs from fromJust
in the sense it is not possible
to extract values from monoid
fromMonoid :: (Eq a, Monoid a) => a -> a -> a Source #
fromMonoid keeps the monoid value if it is not empty, otherwise it replaces it with the provided default value
Note: No check is made to see if default value is itself mempty
Note: This differs from fromMaybe
in the sense it is not possible
to extract values from monoid
Note: similar to flip |
for the appropriate types.
(?+) :: (Eq a, Monoid a) => a -> a -> a infixr 1 Source #
Infix fromMonoid. Equivalent to higher order ternary operator,
similar to python if
in expressions
Example usage:
let x = valueThatCanBeEmpty ?+ defaultValue
(<!>) :: (Eq a, Monoid a) => a -> a -> a infixl 3 Source #
Monoid choice operator. See (obligatory reading, even if you don't understand it at first): http://stackoverflow.com/questions/13080606/confused-by-the-meaning-of-the-alternative-type-class-and-its-relationship-to
This operator implements Alternative
like choice operator to Monoid
s.
listToMonoid :: Monoid a => [a] -> a Source #
listToMonoid extracts the first element from a monoid list into a single monoid, or returns mempty if the list is empty
Note: This differs from listToMaybe
in the sense it is not possible
to promote values into a monoid
listToMonoid = headDef mempty
monoidToList :: (Eq a, Monoid a) => a -> [a] Source #
monoidToList convert an empty monoid into an empty list, otherwise it creates a singleton list with the monoid inside
Note: This differs from maybeToList
in the sense it is not possible
to extract the value from a monoid
monoidToList = monoid [] singleton
catMonoids :: (Eq a, Monoid a) => [a] -> [a] Source #
Filter out all empty monoids from a list.
catMonoids = filter isNotEmpty
mapMonoid :: (Eq b, Monoid b) => (a -> b) -> [a] -> [b] Source #
Apply a function that returns a monoid to all elements of a list and return a new list with only not mempty results.
Note: This differs from mapMaybe
in the sense it is not possible
to extract the value from a monoid.
getFirst' :: (Eq a, Monoid a) => [a] -> a Source #
Get the first non-empty element from a list. If all elements are mempty
,
or the list is empty, it returns mempty
.
Note: A newtype based solution as done by maybe in Data.Monoid will
always be more efficient than this, so this is not really recommend.
However, it might come handy in some non-critical code.
getLast' :: (Eq a, Monoid a) => [a] -> a Source #
Get the last non-empty element from a list. If all elements are mempty
,
or the list is empty, it returns mempty
.
Note: A newtype based solution as done by maybe in Data.Monoid will
always be more efficient than this, so this is not really recommend.
However, it might come handy in some non-critical code.
atF :: (Foldable t, Monoid a) => t a -> Int -> a Source #
A '(!!)'
that fails returning
.mempty
Note: this function starts by mapping the foldable structure to a list...
Bool
Some extra functions included, namely the simplified ternary operator modified from what is seen in https://gist.github.com/Burgestrand/218987
Note: This is probably not considered good practice.
Use the standard if-then-else
instead, its almost always clearer.
You have been warned.
fromBool :: a -> Bool -> a -> a Source #
fromBool is a 'if' rewrite following the call convention of fromMaybe.
fromBoolC :: a -> (a -> Bool) -> a -> a Source #
fromBoolC is similar to fromBool
, but it takes a condition rather
than a simple boolean value
catBools :: [Bool] -> [Bool] Source #
Cat bools. Filter out False values from a list. Probably useless.
catBools = filter id
(?) :: Bool -> a -> a -> a infixr 1 Source #
Ternary operator. Use like this:
(i > 0) ? i $ 1
Note: this is non-idiomatic haskell. Use at your own risk.
Note: this may require additional parenthesis, so it may not be worth it.
(?$) :: (a -> Bool) -> a -> a -> a infixr 1 Source #
Higher order ternary operator. Use like this:
(not . null) ?$ "" $ "default value"
Note: this is non-idiomatic haskell. Use at your own risk.
(?|) :: a -> (a -> Bool) -> a -> a infixr 1 Source #
Higher order ternary operator, similar to python if
in expressions.
Use like this:
"" ?| (not . null) $ "default value"
Note: this is non-idiomatic haskell. Use at your own risk.
boolToMaybe :: a -> Bool -> Maybe a Source #
Provided a default value, apply it to a maybe if the predicate holds
ifToMaybe :: Bool -> a -> Maybe a Source #
Same as boolToMaybe, but with a more familiar 'if-like' syntax
boolCToMaybe :: a -> (a -> Bool) -> Maybe a Source #
Test a value with a function returning a Bool, and apply it to a Maybe accordingly.
ifCToMaybe :: (a -> Bool) -> a -> Maybe a Source #
Same as boolCToMaybe, but with a more familiar 'if-like' syntax
boolToEither :: a -> b -> Bool -> Either a b Source #
Provided two values, choose amongst them based on a Bool
value.
\l r b = if b then Right r else Left l
boolCToEither :: a -> b -> (b -> Bool) -> Either a b Source #
Provided two values, choose amongst them based on a the provided test on the second value.
\l r f = if f r then Left l else Right r
boolToList :: a -> Bool -> [a] Source #
boolCToList :: a -> (a -> Bool) -> [a] Source #
Insert the provided value into a list if the provided condition is
True
, otherwise return an empty list.
Use a list comprehension instead:
[value | f value]
boolToMonoid :: Monoid a => a -> Bool -> a Source #
boolCToMonoid :: Monoid a => a -> (a -> Bool) -> a Source #
(?&&) :: Monoid a => a -> Bool -> a infixl 1 Source #
Emulates and
,&&
and or
,||
from scripting languages like python,
in the sense you can mix booleans with a value to get the value when
the boolean is true (or mempty
otherwise).
However, in order to allow several
in a row, the order
is not the one normally used in languages like bash, where the test comes
first.?&&
Usage:
value ?&& bool1 ?&& bool2 ?&& ...
Note: this is non-idiomatic haskell. Use at your own risk. You should instead use the following code :
if bool1 && bool2 && ... then value else mempty
Or better yet:
if and [bool1,bool2,...] then value else mempty
(?&&\) :: Monoid a => a -> (a -> Bool) -> a infixl 1 Source #
Emulates and
,&&
and or
,||
from scripting languages like python,
in the sense you can mix boolean tests with a value to get the original
value when all the tests return true (or mempty
otherwise).
However, in order to allow several
in a row, the order
is not the one normally used in languages like bash, where the test comes
first.??&&
Note: an easy mnemonic to remember is that operators ending in \ (lambda) imply that their parameters are functions instead of values (in this particular case, boolean tests)
Usage:
value ?&&\ condition1 ?&&\ condition2 ?&&\ ...
Note: this is non-idiomatic haskell. Use at your own risk.
allCond :: a -> [a -> Bool] -> Bool Source #
Apply a list of boolean checks/tests to a variable, and return (True) if all of them passed.
Note: See All
in Data.Monoid and all
in Prelude for reference.
See: http://www.haskell.org/pipermail/haskell-cafe/2007-February/022694.html
anyCond :: a -> [a -> Bool] -> Bool Source #
Apply a list of boolean checks/tests to a variable, and return (True) if any of them passed.
Note: See Any
in Data.Monoid and any
in Prelude for reference.
See: http://www.haskell.org/pipermail/haskell-cafe/2007-February/022694.html