Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
This module allows you to zip lists with any Traversable
data structure.
It's intended that you import it qualified:
import qualified Data.Traversable.HeteroZip as Hetero x = Hetero.zipWith ...
Synopsis
- zip :: Traversable t => [a] -> t b -> t (Maybe a, b)
- zipErr :: (HasCallStack, Traversable t) => [a] -> t b -> t (a, b)
- zipInf :: Traversable t => Infinite a -> t b -> t (a, b)
- zipMay :: Traversable t => [a] -> t b -> t (Maybe (a, b))
- zipNote :: (HasCallStack, Traversable t) => String -> [a] -> t b -> t (a, b)
- zipWith :: Traversable t => (Maybe a -> b -> c) -> [a] -> t b -> t c
- zipWithErr :: (HasCallStack, Traversable t) => (a -> b -> c) -> [a] -> t b -> t c
- zipWithInf :: Traversable t => (a -> b -> c) -> Infinite a -> t b -> t c
- zipWithMay :: Traversable t => (a -> b -> c) -> [a] -> t b -> t (Maybe c)
- zipWithNote :: (HasCallStack, Traversable t) => String -> (a -> b -> c) -> [a] -> t b -> t c
- enumerate :: Traversable t => t a -> t (Int, a)
- enumerateWith :: Traversable t => (Int -> a -> b) -> t a -> t b
- setHoles :: Functor f => (a -> g b) -> f a -> Compose f g b
- unsetHoles :: Functor f => (g a -> b) -> Compose f g a -> f b
Zipping
A Traversable
's elements can be visited one at a time, and updated
in-place. That means we can visit them at the same time as we walk along a
list, and use the values in the list to update the values in the
Traversable
. These functions do just that.
zip*
functions simply pair elements off, while zipWith*
functions use an
explicit combining function, like regular zip
and
zipWith
. They each have five variants to deal with the possibility
that the input list is shorter than the Traversable
:
zip
andzipWith
pass aMaybe
to the combining function.zipWith
is the most general function here; all the others can be implemented as simple wrappers around that.zipMay
andzipWithMay
putMaybe
s in the resultTraversable
.zipErr
andzipWithErr
are partial, throwing errors if the list is too short.zipNote
andzipWithNote
are also partial, with a custom error message.zipInf
andzipWithInf
use anInfinite
list that will never be too short.
All these functions are lazy in both the list and Traversable
arguments,
and in the function application, to the extent that the Traversable
instance allows. For example:
>>>
take 3 $ zip ([1, 2, 3] ++ undefined) ([1, 2, 3] ++ undefined)
[(Just 1,1),(Just 2,2),(Just 3,3)]>>>
fst <$> zip [1, 2, 3] [1, 2, undefined]
[Just 1,Just 2,Just 3]>>>
isJust . fst <$> zip [1, 2, undefined] [1, 2, undefined]
[True,True,True]>>>
snd <$> zip [1, 2, undefined] [1, 2, 3]
[1,2,3]
zip :: Traversable t => [a] -> t b -> t (Maybe a, b) Source #
Zip a list with any Traversable
, maintaining the shape of the latter.
If the list is too short, pair with Just
values until it runs out, and then
Nothing
s.
>>>
zip [1, 2] (Just ())
Just (Just 1,())
>>>
zip [] (Just ())
Just (Nothing,())
>>>
zip [] Nothing
Nothing
zipErr :: (HasCallStack, Traversable t) => [a] -> t b -> t (a, b) Source #
Zip a list with any Traversable
, maintaining the shape of the latter.
If the list is too short, throw an error.
>>>
zipErr [1, 2] (Just ())
Just (1,())
>>>
zipErr [] (Just ())
Just (*** Exception: zipErr: list too short CallStack (from HasCallStack): zipErr, called at ...
>>>
zipErr [] Nothing
Nothing
zipInf :: Traversable t => Infinite a -> t b -> t (a, b) Source #
Zip an Infinite
list with any Traversable
, maintaining the shape of the
latter.
>>>
:set -XPostfixOperators
>>>
import Data.List.Infinite ((...))
>>>
zipInf (1...) (Just ())
Just (1,())
>>>
zipInf (1...) Nothing
Nothing
zipMay :: Traversable t => [a] -> t b -> t (Maybe (a, b)) Source #
Zip a list with any Traversable
, maintaining the shape of the latter.
If the list is too short, start producing Nothing
s. You can use sequence
to get a
; but note that this must walk the whole
Maybe
(t (a, b))Traversable
before it can produce a Just
.
>>>
zipMay [1, 2] (Just ())
Just (Just (1,()))
>>>
zipMay [] (Just ())
Just Nothing
>>>
zipMay [] Nothing
Nothing
zipNote :: (HasCallStack, Traversable t) => String -> [a] -> t b -> t (a, b) Source #
Zip a list with any Traversable
, maintaining the shape of the latter.
If the list is too short, throw an error with a custom error string.
>>>
zipNote "oops" [1, 2] (Just ())
Just (1,())
>>>
zipNote "oops" [] (Just ())
Just (*** Exception: oops CallStack (from HasCallStack): zipNote, called at ...
>>>
zipNote "oops" [] Nothing
Nothing
zipWith :: Traversable t => (Maybe a -> b -> c) -> [a] -> t b -> t c Source #
Use a given function to zip a list with any Traversable
, maintaining the
shape of the latter.
If the list is too short, pass Just
values until it runs out, and then
Nothing
s.
>>>
zipWith (maybe id (+)) [1, 2] (Just 10)
Just 11
>>>
zipWith (maybe id (+)) [] (Just 10)
Just 10
>>>
zipWith (maybe id (+)) [] Nothing
Nothing
zipWithErr :: (HasCallStack, Traversable t) => (a -> b -> c) -> [a] -> t b -> t c Source #
Use a given function to zip a list with any Traversable
, maintaining the
shape of the latter.
If the list is too short, throw an error.
>>>
zipWithErr (+) [1, 2] (Just 10)
Just 11
>>>
zipWithErr (+) [] (Just 10)
Just *** Exception: zipWithErr: list too short CallStack (from HasCallStack): zipWithErr, called at ...
>>>
zipWithErr (+) [] Nothing
Nothing
zipWithInf :: Traversable t => (a -> b -> c) -> Infinite a -> t b -> t c Source #
Use a given function to zip an Infinite
list with any Traversable
,
maintaining the shape of the latter.
>>>
:set -XPostfixOperators
>>>
import Data.List.Infinite ((...))
>>>
zipWithInf (+) (1...) (Just 10)
Just 11
>>>
zipWithInf (+) (1...) Nothing
Nothing
zipWithMay :: Traversable t => (a -> b -> c) -> [a] -> t b -> t (Maybe c) Source #
Use a given function to zip a list with any Traversable
, maintaining the
shape of the latter.
If the list is too short, start producing Nothing
s. You can use sequence
to get a
; but note that this must walk the whole
Maybe
(t c)Traversable
before it can produce a Just
.
>>>
zipWithMay (+) [1, 2] (Just 10)
Just (Just 11)
>>>
zipWithMay (+) [] (Just 10)
Just Nothing
>>>
zipWithMay (+) [] Nothing
Nothing
zipWithNote :: (HasCallStack, Traversable t) => String -> (a -> b -> c) -> [a] -> t b -> t c Source #
Use a given function to zip a list with any Traversable
, maintaining the
shape of the latter.
If the list is too short, throw an error with a custom error string.
>>>
zipWithNote "oops" (+) [1, 2] (Just 10)
Just 11
>>>
zipWithNote "oops" (+) [] (Just 10)
Just *** Exception: oops CallStack (from HasCallStack): zipWithNote, called at ...
>>>
zipWithNote "oops" (+) [] Nothing
Nothing
Enumeration
If all you want is to number off elements starting from 0
, these functions
are convenient.
enumerate :: Traversable t => t a -> t (Int, a) Source #
Pair any Traversable
with the Int
s starting from 0
.
>>>
enumerate (Just ())
Just (0,())
>>>
enumerate "abc"
[(0,'a'),(1,'b'),(2,'c')]
enumerateWith :: Traversable t => (Int -> a -> b) -> t a -> t b Source #
Use a given function to pair any Traversable
with the Int
s starting
from 0
.
>>>
enumerateWith (+) (Just 3)
Just 3
>>>
enumerateWith replicate "abc"
["","b","cc"]
Holes
The "holes" in a Traversable
structure are the positions that hold
traversable elements. For example, if you call toList
, the result
contains all the values that were in holes; if you fmap
, the values in
holes get updated, while everything else stays fixed.
We can use Compose
to combine the holes of two Traversable
s. If we have
xs :: f (g a)
where f
and g
are both Traversable
, then the holes of
xs
are given by the
instance, and have type Traversable
fg a
. The
holes of
are the holes of the Compose
xs :: Compose
f g ag
s that
are themselves in the holes of the f
, and have type a
.
For example, the holes in these data structures are bolded:
-- Compose [] withMaybe
: [Just 1, Nothing, Just 2, Nothing] :: [Maybe Int] Compose [Just 1, Nothing, Just 2, Nothing] :: Compose [] Maybe Int -- Compose ((,) a) with []: (True, [1, 2, 3]) :: (Bool, [Int]) Compose (True, [1, 2, 3]) :: Compose ((,) Bool) [] Int -- Compose (Either
a) with []: Left [1, 2] :: Either [Int] [Int] Right [1, 2] :: Either [Int] [Int] Compose (Left [1, 2]) :: Compose (Either [Int]) [] Int Compose (Right [1, 2]) :: Compose (Either [Int]) [] Int -- NestedCompose
: Compose [Just (Just 1), Just Nothing, Nothing] :: Compose [] Maybe (Maybe Int) Compose (Compose [Just (Just 1), Just Nothing, Nothing]) :: Compose (Compose [] Maybe) Maybe Int
When zipping, holes are relevant because every hole gets paired with exactly
one list element. You can use setHoles
and unsetHoles
to control the
pairing-off.
With
, setHoles
f xf
gets called once for every hole in x
; and every
hole returned by every call to f
will be a hole. So if f
returns...
- ...
, then only theMaybe
aJust
values will be holes. - ...
, then only theEither
a bRight
values will be holes. - ...
(a, b)
, then only thesnd
values will be holes. - ...
[a]
, then every list element will be a hole.
And
acts as an inverse; unsetHoles
g xg
gets called on parts of x
that may have any number of holes, and whatever g
returns will become a
single hole in its own right.
>>>
let xs = [Just 10, Nothing, Just 20, Nothing]
>>>
enumerate xs
[(0,Just 10),(1,Nothing),(2,Just 20),(3,Nothing)]>>>
-- Only enumerate the `Just` values:
>>>
unsetHoles id $ enumerate $ setHoles id xs
[Just (0,10),Nothing,Just (1,20),Nothing]
>>>
let xs = [11,22..66]
>>>
zipWithErr (+) [1..] xs
[12,24,36,48,60,72]>>>
-- Only add to the even numbers:
>>>
:{
unsetHoles (either id id) $ zipWithErr (+) [1..] $ setHoles (\x -> if even x then Right x else Left x) $ xs :} [11,23,33,46,55,69]
setHoles :: Functor f => (a -> g b) -> f a -> Compose f g b Source #
Set the holes in a Traversable
by wrapping in Compose
.
setHoles f x =Compose
(fmap
f x)
unsetHoles :: Functor f => (g a -> b) -> Compose f g a -> f b Source #
Simplify the holes in a Traversable
by unwrapping from Compose
.
unsetHoles f x =fmap
f (getCompose
x)
A note on Traversable
A Traversable
structure x :: t a
can be decomposed into
It can then be reconstructed from these. Or, given another list [b]
of the
same length, we can use the original spine to create a t b
with these new
elements, of the same shape as the original.
is the function that reconstructs it. That is,zipWithErr
const
zipWithErr
const
(elementList x) (spine x) === x
allows you to exactly recreate the original structure, or to replace its element list by providing a different one.