Copyright | (c) David James 2020 |
---|---|
License | BSD3 |
Stability | Experimental |
Safe Haskell | None |
Language | Haskell2010 |
Provides fmap
-like functionality, but can also "inject" additional parameters to the mapping function, such as:
- whether the first / last item
- the previous / next item
- the index from the start / end
It offers excellent performance.
Synopsis
- withFirst :: Traversable t => (a -> Bool -> b) -> t a -> t b
- withLast :: Traversable t => (a -> Bool -> b) -> t a -> t b
- withFirstLast :: Traversable t => (a -> Bool -> Bool -> b) -> t a -> t b
- andFirstLast :: Traversable t => t a -> t (a, Bool, Bool)
- withPrevNext :: Traversable t => (a -> Maybe a -> Maybe a -> b) -> t a -> t b
- andPrevNext :: Traversable t => t a -> t (a, Maybe a, Maybe a)
- mapWith :: Traversable t => InjectedFn a b -> t a -> t b
- mapWithM :: (Traversable t, Monad m) => InjectedFn a (m b) -> t a -> m (t b)
- mapWithM_ :: (Traversable t, Monad m) => InjectedFn a (m b) -> t a -> m ()
- foldMapWith :: (Traversable t, Monoid b) => InjectedFn a b -> t a -> b
- data InjectedFn a b
- class Injectable m where
- (^->) :: CurryTF i b => m a (FnType i b) -> Injector a i -> InjectedFn a b
- (<-^) :: CurryTF i b => m a (FnType i b) -> Injector a i -> InjectedFn a b
- isLim :: Injector a (App1 Bool)
- adjElt :: Injector a (App1 (Maybe a))
- adj2Elts :: Injector a (App2 (Maybe a) (Maybe a))
- eltIx :: Integral i => Injector a (App1 i)
- evenElt :: Injector a (App1 Bool)
- foldlElts :: (i -> a -> i) -> i -> Injector a (App1 i)
- foldl1Elts :: (a -> a -> a) -> Injector a (App1 a)
- eltFrom :: [i] -> Injector a (App1 i)
- eltFromMay :: [i] -> Injector a (App1 (Maybe i))
- eltFromDef :: i -> [i] -> Injector a (App1 i)
- isFirst :: Injectable f => f a (Bool -> b) -> InjectedFn a b
- isLast :: Injectable f => f a (Bool -> b) -> InjectedFn a b
- prevElt :: Injectable f => f a (Maybe a -> b) -> InjectedFn a b
- nextElt :: Injectable f => f a (Maybe a -> b) -> InjectedFn a b
- data Injector a i = Injector (a -> s -> (s, i)) s
- type App4 a b c d = (a, (b, (c, (d, ()))))
- type App3 a b c = (a, (b, (c, ())))
- type App2 a b = (a, (b, ()))
- type App1 a = (a, ())
- app1 :: a -> App1 a
- app2 :: a -> b -> App2 a b
- app3 :: a -> b -> c -> App3 a b c
- app4 :: a -> b -> c -> d -> App4 a b c d
Type Names
These names are used for types and variables throughout:
t
- the
Traversable
we're mapping over a
- a value in the input
Traversable
b
- a result in the output
Traversable
i
- an output from an
Injector
, injected into a map function. (i may represent one than one injected value). s
- the internal state in an
Injector
Pre-Packaged Maps
Some pre-defined maps with commonly used injectors.
withFirst :: Traversable t => (a -> Bool -> b) -> t a -> t b Source #
Maps over a Traversable
, with an additional parameter indicating whether an item is the first.
>>>
let g x f = [if f then '*' else ' ', x] in withFirst g "fred"
["*f", " r", " e", " d"]
withLast :: Traversable t => (a -> Bool -> b) -> t a -> t b Source #
Maps over a Traversable
, with an additional parameter indicating whether an item is the last.
>>>
let g x l = [x, if l then '*' else ' '] in withLast g "fred"
["f ","r ","e ","d*"]
withFirstLast :: Traversable t => (a -> Bool -> Bool -> b) -> t a -> t b Source #
Maps over a Traversable
, with additional parameters indicating whether an item is the first or last (or both).
>>>
let g x f l = [star f, x, star l]; star b = if b then '*' else ' ' in withFirstLast g "fred"
["*f ", " r ", " e ", " d*"]
andFirstLast :: Traversable t => t a -> t (a, Bool, Bool) Source #
andFirstLast = withFirstLast (,,)
withPrevNext :: Traversable t => (a -> Maybe a -> Maybe a -> b) -> t a -> t b Source #
Maps over a Traversable
, with additional parameters indicating the previous and next elements.
The second (or third) parameter to the map function is Nothing
when called for the first (or last) item, otherwise it's Just
the previous (or next) item.
>>>
let f x prvMay nxtMay = maybe "*" (cmp x) prvMay ++ x ++ maybe "*" (cmp x) nxtMay; cmp x y = show $ compare x y in withPrevNext f ["foo", "bar", "baz"]
["*fooGT","LTbarLT","GTbaz*"]
andPrevNext :: Traversable t => t a -> t (a, Maybe a, Maybe a) Source #
andPrevNext = withPrevNext (,,)
Custom Maps
In general, a map function will take one parameter from the Traversable
, then one (or more) from each of any number of Injector
s. For example:
>>>
mapFn w x y z = (w, x, y, z)
>>>
injectedFn = mapFn <-^ isLim ^-> eltIx <-^ eltFrom [8,2,7,1]
>>>
mapWith injectedFn "abc"
[('a',False,0,7),('b',False,1,2),('c',True,2,8)]
Where:
mapFn
: a function that maps over aTraversable
, but requires additional parametersinjectedFn
: represents the combination ofmapFn
with three injectors that provide the required parameters:
mapWith
then maps the mapFn
over the Traversable
, with the following parameters:
Call | w | x | y | z |
---|---|---|---|---|
1 | 'a' | False | 0 | 7 |
2 | 'b' | False | 1 | 2 |
3 | 'c' | True | 2 | 8 |
mapWith :: Traversable t => InjectedFn a b -> t a -> t b Source #
maps an InjectedFn
over a Traversable
type t
, turning a t a
into a t b
and preserving the structure of t
.
Parameters (as defined in the InjectedFn
) are passed to a map function (embedded in the InjectedFn
), in addition to the elements of the Traversable
.
mapWithM :: (Traversable t, Monad m) => InjectedFn a (m b) -> t a -> m (t b) Source #
like mapM
, but with an InjectedFn
.
mapWithM_ :: (Traversable t, Monad m) => InjectedFn a (m b) -> t a -> m () Source #
like mapM_
(which is like mapM
but ignores the results), but with an InjectedFn
.
foldMapWith :: (Traversable t, Monoid b) => InjectedFn a b -> t a -> b Source #
like foldMap
, but with an InjectedFn
data InjectedFn a b Source #
Represents a function from a
, plus a number of injected values, to b
.
Used by mapWith
(& related), which maps over a Traversable
, injecting the additional values as it goes.
Constructed by combining a map function with Injector
s using the ^->
and <-^
operators.
The sequence:
(a -> i1 -> i2 -> ... -> in -> b) op1 inj1 op2 inj2 ... opn injn
where:
produces an
, with n injected values (or more if any of the injectors inject multiple values).InjectedFn
a b
Instances
Injectable InjectedFn Source # | |
Defined in MapWith (^->) :: CurryTF i b => InjectedFn a (FnType i b) -> Injector a i -> InjectedFn a b Source # (<-^) :: CurryTF i b => InjectedFn a (FnType i b) -> Injector a i -> InjectedFn a b Source # |
class Injectable m where Source #
An Injectable
is (recursively) either:
- a function
(a -> i1 [.. -> in] -> b)
; or - an
InjectedFn a (i1 [.. -> in] -> b)
, created byInjectable
opInjector
When n
is the number of parameters injected by an injector (most commonly 1).
(^->) :: CurryTF i b => m a (FnType i b) -> Injector a i -> InjectedFn a b infixl 1 Source #
Inject "from the left"
(<-^) :: CurryTF i b => m a (FnType i b) -> Injector a i -> InjectedFn a b infixl 1 Source #
Inject "from the right"
Instances
Injectable InjectedFn Source # | |
Defined in MapWith (^->) :: CurryTF i b => InjectedFn a (FnType i b) -> Injector a i -> InjectedFn a b Source # (<-^) :: CurryTF i b => InjectedFn a (FnType i b) -> Injector a i -> InjectedFn a b Source # | |
Injectable ((->) :: Type -> Type -> Type) Source # | |
Predefined Injectors
Use these (or custom Injector
s) to create InjectedFn
s that can be used with mapWith
isLim :: Injector a (App1 Bool) Source #
inject True
if the item is at the limit:
- from the left: if it's the first item
- from the right: if it's the last item
else inject False.
>>>
let f a l = [a, if l then '*' else ' '] in mapWith (f ^-> isLim) "12345"
["1*","2 ","3 ","4 ","5 "]>>>
let f a l = [a, if l then '*' else ' '] in mapWith (f <-^ isLim) "12345"
["1 ","2 ","3 ","4 ","5*"]
adjElt :: Injector a (App1 (Maybe a)) Source #
inject Just
the adjacent item:
- from the left: the previous item, except for the first item
- from the right: the next item, except for the last item. (The "previous from the right" is the "next".)
inject Nothing
if there is no adjacent item (i.e. for the first / last).
>>>
let f a b = [a,maybe '-' id b] in mapWith (f ^-> adjElt) "12345"
["1-","21","32","43","54"]>>>
let f a b = [a,maybe '-' id b] in mapWith (f <-^ adjElt) "12345"
["12","23","34","45","5-"]
adj2Elts :: Injector a (App2 (Maybe a) (Maybe a)) Source #
like adjElt
, but injects the two adjacent items into separate parameters.
>>>
let f a b c = [a,ch b,ch c]; ch = maybe '-' id in mapWith (f ^-> adj2Elts) "12345"
["1--","21-","321","432","543"]>>>
let f a b c = [a,ch b,ch c]; ch = maybe '-' id in mapWith (f <-^ adj2Elts) "12345"
["123","234","345","45-","5--"]
eltIx :: Integral i => Injector a (App1 i) Source #
inject the item index:
- from the left: the first item is 0, the second 1, etc.
- from the right: the last item is 0, the penultimate 1, etc.
>>>
let f a b = a : show b in mapWith (f ^-> eltIx) "freddy"
["f0","r1","e2","d3","d4","y5"]>>>
let f a b = a : show b in mapWith (f <-^ eltIx) "freddy"
["f5","r4","e3","d2","d1","y0"]
evenElt :: Injector a (App1 Bool) Source #
True if an even-numbered (0th, 2nd, 4th, etc) item, counting from the left or from the right.
>>>
let f a e = [a, if e then '*' else ' '] in mapWith (f ^-> evenElt) "012345"
["0*","1 ","2*","3 ","4*","5 "]>>>
let f a e = [a, if e then '*' else ' '] in mapWith (f <-^ evenElt) "543210"
["5 ","4*","3 ","2*","1 ","0*"]
foldlElts :: (i -> a -> i) -> i -> Injector a (App1 i) Source #
Inject a (left-associative) fold of the items:
Item | Injected Value | |
---|---|---|
from the left | from the right | |
a0 | z `acc` a0 | ((z `acc` an) `acc` .. a1) `acc` a0 |
a1 | (z `acc` a0) `acc` a1 | (z `acc` an) `acc` .. a1 |
.. | ||
an | ((z `acc` a0) `acc` a1) `acc` .. an | z `acc` an |
>>>
let f a b = a ++ show b in mapWith (f ^-> foldlElts (\l s -> l + length s) 0) ["every", "good", "boy"]
["every5","good9","boy12"]>>>
let f a b = a ++ show b in mapWith (f <-^ foldlElts (\l s -> l + length s) 0) ["every", "good", "boy"]
["every12","good7","boy3"]
foldl1Elts :: (a -> a -> a) -> Injector a (App1 a) Source #
A variant of foldlElts
that has no starting value:
Item | Injected Value | |
---|---|---|
from the left | from the right | |
a0 | a0 | (an `acc` .. a1) `acc` a0 |
a1 | a0 `acc` a1 | an `acc` .. a1 |
.. | ||
an | (a0 `acc` a1) `acc` .. an | an |
>>>
mapWith ((,) ^-> foldl1Elts (-)) [10,1,3]
[(10,10),(1,9),(3,6)]>>>
mapWith ((,) <-^ foldl1Elts (-)) [10,1,3]
[(10,-8),(1,2),(3,3)]
Inject each given element in turn:
- from the left: the first element will be injected for the first item in the
Traversable
. - from the right: the first element will be injected for the last item in the
Traversable
.
>>>
let f a b = [a,b] in mapWith (f ^-> eltFrom "bill") "sue"
["sb","ui","el"]>>>
let f a b = [a,b] in mapWith (f <-^ eltFrom "bill") "sue"
["sl","ui","eb"]
As a result of laziness, it is not always an error if there are not enough elements, for example:
>>>
drop 1 $ mapWith ((\_ i -> i) <-^ eltFrom [8,2]) "abc"
[2,8]
eltFromMay :: [i] -> Injector a (App1 (Maybe i)) Source #
a safe version of eltFrom
. Injects Just
each given element in turn, or Nothing
after they've been exhausted.
>>>
let f a b = [a,ch b]; ch = maybe '-' id in mapWith (f ^-> eltFromMay "ben") "sally"
["sb","ae","ln","l-","y-"]>>>
let f a b = [a,ch b]; ch = maybe '-' id in mapWith (f <-^ eltFromMay "ben") "sally"
["s-","a-","ln","le","yb"]
eltFromDef :: i -> [i] -> Injector a (App1 i) Source #
a safe version of eltFrom
. Injects each given element in turn, or the default after they've been exhausted.
>>>
let f a b = [a,b] in mapWith (f ^-> eltFromDef 'X' "ben") "sally"
["sb","ae","ln","lX","yX"]>>>
let f a b = [a,b] in mapWith (f <-^ eltFromDef 'X' "ben") "sally"
["sX","aX","ln","le","yb"]
Pre-Combined Injectors
These are combinations of ^->
or <-^
with pre-defined injectors.
They work well with the &
operator, and can be combined with the ^->
and <-^
operators e.g.:
mapWith (f & isFirst <-^ eltFrom [9,2]) == mapWith (f ^-> isLim <-^ eltFrom [9,2])
You may find them more memorable or easier to type.
isFirst :: Injectable f => f a (Bool -> b) -> InjectedFn a b Source #
isLim
, from the left.
isLast :: Injectable f => f a (Bool -> b) -> InjectedFn a b Source #
isLim
, from the right.
prevElt :: Injectable f => f a (Maybe a -> b) -> InjectedFn a b Source #
adjElt
, from the left.
nextElt :: Injectable f => f a (Maybe a -> b) -> InjectedFn a b Source #
adjElt
, from the right.
Custom Injectors
An Injector a i
can be used with mapWith
to map over a Traversable
containing elements of type a
, injecting values according to the type i
as it goes.
Injectors have an initial state and a generate function.
For each item in the Traversable
, the generate function can use both:
- the item from the
Traversable
, and - the current state
to determine both:
- the new state, and
- the injection value(s)
The injection value(s) must be an args
(per CurryTF
), in order for the injector to work with the ^->
and <-^
operators.
These can be created by:
- (recommended) using
app1
,app2
, etc; - by nesting the values appropriately e.g
(i1, ())
or(i1, (i2, (i3, (i4, (i5, .. () ..)))))
; or - defining a new instance of
CurryTF
The first value(s) to inject is/are determined by a first call to the generate function.
The first call to the generate function is with the first (if combined with ^->
) or last (if combined with <-^
) item from the Traversable
and the initial state.
For example:
>>>
funnyNext a s = (a + 1, app1 $ a + s)
>>>
funnyInjector = Injector funnyNext 17
>>>
mapWith ((\_ i -> i) ^-> funnyInjector) [4,8,3]
[21,13,12]
Call | Initial State | Item | New State | Injection |
---|---|---|---|---|
1 | 17 | 4 | 4+1=5 | 17+4=21 |
2 | 5 | 8 | 8+1=9 | 5+8=13 |
3 | 9 | 3 | 3+1=4 (ignored) | 9+3=12 |
>>>
mapWith ((\_ i -> i) <-^ funnyInjector) [4,8,3]
[13,12,20]
Call | Initial State | Item | New State | Injection |
---|---|---|---|---|
1 | 17 | 3 | 3+1=4 | 17+3=20 |
2 | 4 | 8 | 8+1=9 | 4+8=12 |
3 | 9 | 4 | 4+1=5 (ignored) | 9+4=13 |
More usefully, this might allow for e.g. injection of random values, etc.
Injector (a -> s -> (s, i)) s | the first parameter is a generate function, the second parameter is the initial/prior state. |
Stacked-Tuple Helpers
These make it easier to define Injector
types and injection values. For example:
>>>
myInj = Injector (\_ _ -> ((), app3 7 False 'z')) () :: Injector a (App3 Int Bool Char)
defines an Injector
, that can map over a Traversable
containing any type, and inject three additional constant parameters: 7::Int
, False::Bool
and 'z'::Char
. Then:
>>>
mapWith ((,,,) ^-> myInj) ["foo", "bar", "baz"]
[("foo",7,False,'z'),("bar",7,False,'z'),("baz",7,False,'z')]
You are advised to use these since I'm considering re-working CurryTF so that it's not based on tuples. If I do, I intend to maintain compatibility of app1/App1, etc.
Performance
I think the performance is now (since 0.2.0.0) excellent. In particular:
mapWith
"traverses" in each direction at most once, and only goes in both directions if it needs to;- many functions are inlinable and "compile away"; and
- mapWith is capable of fusion (see details below).
If you have any examples where you think performance is poor, or suggestions for improvements, please let me know.
Benchmarks
I've compared the performance of mapWith
vs markbounds
and a number of other attempts to "hand craft" equivalent functionality.
The results are in Benchmarks.ods.
The Benchmarks.hs file contains the details of these tests.
Fusion
mapWith
& friends are capable of list fusion.
When the Traversable
is a List, mapWith
is always a "good consumer". When the only injections are "from the left", it is also a "good producer".
As a result, code like:
>>>
let f n b = if b then n*2 else n*3 in sum $ mapWith (f ^-> evenElt) [1..1000000]
will compile to a loop with no generation of list elements and no call stack usage.
When a "from the right" injection occurs, mapWith
is not a "good producer", and an intermediate list will be created.
However, with a "state free" Injector
(such as isLim
or adjElt
), the list elements will only exist temporarily, the call stack will not grow
(see here),
and there is no limit to the number of elements in the processed list.
With other "from the right" Injectors, the call stack will grow as elements are processed, giving a limit to the size of the list. Despite this, I think the performance remains very good, and better than many alternative approaches.
In summary, when mapWith
sits between a "good producer" and a "good consumer", there are three broad categories of behaviour:
Injections | Speed | Size limit |
---|---|---|
only "from the left" | exceptional | No |
"from the right", but only "state free" | very good | No |
any | good | Yes |
Note that eltFrom
(and similar) are not a "good consumers".