Taking a list of lists and generating all variants with one element replaced [closed] - haskell

Closed. This question needs to be more focused. It is not currently accepting answers.
Want to improve this question? Update the question so it focuses on one problem only by editing this post.
Closed 5 years ago.
Improve this question
I have types for a two-dimensional map of characters:
type Row = [Char]
type Mappy = [Row]
I'd like to write a function that takes a Mappy like:
[['o','o'],['o','o']]
and generates a list of all Mappys with a single 'o' element replaced with 'i':
[ [['i','o'],['o','o']]
, [['o','i'],['o','o']]
, [['o','o'],['i','o']]
, [['o','o'],['o','i']]
]
Here's what I've tried: I think I need to use the map function, because I need to go over each element, but I don't know how, because a map function doesn't keep track of the position it is working on.
type Row = [Char]
type Mappy = [Row]
func :: Mappy -> [Mappy]
func a = map (map someFunc a) a
someFunc :: Mappy -> Char -> Mappy
someFunc a b = if b == "o"
then undefined
else a
Obviously, I should change the undefined, but i have no idea how. Thanks in advance.

Zippers are great, and there's an interesting blog post about
implementing Conway's Game of Life using zippers and comonads in Haskell. On the other
hand, if this is still your first week learning Haskell, you might
want to save Comonads for Thursday, right?
Here's another approach that uses simple recursion and list
comprehensions and no complex Haskell features.
First, imagine we have an awesome function:
varyOne :: (a -> [a]) -> [a] -> [[a]]
varyOne = undefined
that works as follows. Given a function f that produces zero or
more variants of an element a, the function call varyOne f xs
generates all variants of the list xs that result from taking
exactly one element of xs, say x in the middle of the list, and replacing it with all the
variants given by f x.
This function is surprisingly flexible. It can generate the list of all variants resulting from forcibly replacing an element by a constant:
> varyOne (\x -> [3]) [1,2,3,4]
[[3,2,3,4],[1,3,3,4],[1,2,3,4],[1,2,3,3]]
By returning a singleton variant for a specific value and an empty list of variants for other values, it can generate all variants that replace an 'o' with an 'i' while suppressing the "variants" where no replacement is possible:
> let varyRow = varyOne (\c -> if c == 'o' then ['i'] else [])
> varyRow "ooxo"
["ioxo","oixo","ooxi"]
and, because varyRow itself generates variants of a row, it can be used with varyOne to generate variants of tables where a particular row has been replaced by its possible variants:
> varyOne varyRow ["ooo","oox","ooo"]
[["ioo","oox","ooo"],["oio","oox","ooo"],["ooi","oox","ooo"],
["ooo","iox","ooo"],["ooo","oix","ooo"],
["ooo","oox","ioo"],["ooo","oox","oio"],["ooo","oox","ooi"]]
It turns out that this awesome function is surprisingly easy to write:
varyOne :: (a -> [a]) -> [a] -> [[a]]
varyOne f (x:xs)
= [y:xs | y <- f x] ++ [x:ys | ys <- varyOne f xs]
varyOne _ [] = []
The first list comprehension generates all the variants for the current element. The second list comprehension generates variants that involve changes to the right of the current element using a recursive varyOne call.
Given varyOne, we can define:
replaceOne :: Char -> Char -> Mappy -> [Mappy]
replaceOne old new = varyOne (varyOne rep1)
where rep1 x = if x == old then [new] else []
and:
> replaceOne 'o' 'i' ["ooo","oox","ooo"]
[["ioo","oox","ooo"],["oio","oox","ooo"],["ooi","oox","ooo"]
,["ooo","iox","ooo"],["ooo","oix","ooo"]
,["ooo","oox","ioo"],["ooo","oox","oio"],["ooo","oox","ooi"]]
is probably the function you're looking for.
If you prefer to unconditionally replace a single element with i, no matter what the old element was, then this will work:
> varyOne (varyOne (const ['i'])) ["ooo","oox","ooo"]
[["ioo","oox","ooo"],["oio","oox","ooo"],["ooi","oox","ooo"]
,["ooo","iox","ooo"],["ooo","oix","ooo"],["ooo","ooi","ooo"]
,["ooo","oox","ioo"],["ooo","oox","oio"],["ooo","oox","ooi"]]

What you want, young BaasBartMans, is a Zipper.
data Zipper a = Zipper [a] a [a]
ofList :: [a] -> Maybe (Zipper a)
ofList [] = Nothing
ofList (a:as) = Just (Zipper [] a as)
A zipper gives you the context for a position in a list, so you
can easily modify them one at a time, step forward and backward and such.
We can recover a list from a zipper:
instance Foldable Zipper where
foldr f c (Zipper ls a rs) = foldl' (flip f) (f a (foldr f c rs)) ls
We can modify every position in a Zipper simultaneously:
instance Functor Zipper where
fmap f (Zipper ls a rs) = Zipper (fmap f ls) (f a) (fmap f rs)
Or just the focused element:
here :: Functor f => (a -> f a) -> Zipper a -> f (Zipper a)
here f (Zipper ls a rs) = fmap (\a' -> Zipper ls a' rs) (f a)
And as a Zipper is a Comonad, we can modify each element in context:
instance Comonad Zipper where
extract (Zipper _ a _) = a
extend f z#(Zipper ls a rs) = Zipper ls' a' rs' where
a' = f z
ls' = unfoldr (fmap (\z' -> (f z', z')) . goLeft) z
rs' = unfoldr (fmap (\z' -> (f z', z')) . goRight) z
Using that, we can build a function that modifies each element of a list in context:
everywhere :: Alternative f => (a -> f a) -> [a] -> f [a]
everywhere f as = case ofList as of
Nothing -> pure []
Just z -> asum $ extend (fmap toList . here f) z
Which works for simple lists:
λ everywhere (\a -> [a+1]) [10,20,30]
[[11,20,30]
,[10,21,30]
,[10,20,31]]
And nested lists:
λ everywhere (everywhere (\a -> [a+1])) [[10], [20,20], [30,30,30]]
[[[11],[20,20],[30,30,30]]
,[[10],[21,20],[30,30,30]]
,[[10],[20,21],[30,30,30]]
,[[10],[20,20],[31,30,30]]
,[[10],[20,20],[30,31,30]]
,[[10],[20,20],[30,30,31]]]

Related

How can i fix this higher order function code in haskell?

I want to fix this code
h :: (a -> b) -> [a] -> [b]
h f = foldr (\x y -> f x : y) []
if i put h (+100) [1,2,3,4,5] in GHCI
it returns to me [101,202,303,404,505]
when i put h (*10) [1,2,3,4,5] then
i want to get [10,200,3000,40000,500000] list
can anyone help me fixing this code?
You here implemented a map, but in order to repeat the same operation multiple times, you need to perform a mapping on the tail y:
h :: (a -> a) -> [a] -> [a]
h f = foldr (\x y -> f x : map f y) []
Solving the general problem, as Willem Van Onsem's answer does, requires O(n^2) time to calculate the first n elements, because the function has to be applied k times to calculate the kth element.
To solve this sort of problem efficiently, you will need to take advantage of some additional structure. Based on your examples, I think the most obvious approach is to think about semigroup actions. That is, instead of applying an arbitrary function repeatedly, look for an efficient way to represent the compositions of the function. For example, (*x) can be represented by x, allowing (*x) . (*y) to be represented by x*y.
To apply this idea, we first need to transform Willem's solution to make the compositions explicit.
h :: (a -> a) -> [a] -> [a]
h f0 as0 = go as0 f0
where
go [] _ = []
go (a:as) f = f a : go as (f0 . f)
If we like, we can write that as a fold:
h :: (a -> a) -> [a] -> [a]
h f0 as = foldr go stop as f0
where
stop _ = []
go a r f = f a : r (f0 . f)
Now we've structured the function using an accumulator (which is a function). As we compose onto the accumulator, it will get slower and slower to apply it. We want to replace that accumulator with one we can "apply" quickly.
{-# language BangPatterns #-}
import Data.Semigroup
repeatedly :: Semigroup s => (s -> a -> a) -> s -> [a] -> [a]
repeatedly act s0 as = foldr go stop as s0
where
stop _ = []
go a r !s = act s a : r (s0 <> s)
Now you can use, for example,
repeatedly (\(Product s) -> (s*)) (Product 10) [1..5]
==> [10,200,3000,40000,500000]
repeatedly (\(Sum s) -> (s+)) (Sum 100) [1..5]
==> [101,202,303,404,505]
In each of these, you accumulate a product/sum which is added to/multiplied by the current list element.

Mapping while showing intermediate states

I need a function that does this:
>>> func (+1) [1,2,3]
[[2,2,3],[2,3,3],[2,3,4]]
My real case is more complex, but this example shows the gist of the problem. The main difference is that in reality using indexes would be infeasible. The List should be a Traversable or Foldable.
EDIT: This should be the signature of the function:
func :: Traversable t => (a -> a) -> t a -> [t a]
And closer to what I really want is the same signature to traverse but can't figure out the function I have to use, to get the desired result.
func :: (Traversable t, Applicative f) :: (a -> f a) -> t a -> f (t a)
It looks like #Benjamin Hodgson misread your question and thought you wanted f applied to a single element in each partial result. Because of this, you've ended up thinking his approach doesn't apply to your problem, but I think it does. Consider the following variation:
import Control.Monad.State
indexed :: (Traversable t) => t a -> (t (Int, a), Int)
indexed t = runState (traverse addIndex t) 0
where addIndex x = state (\k -> ((k, x), k+1))
scanMap :: (Traversable t) => (a -> a) -> t a -> [t a]
scanMap f t =
let (ti, n) = indexed (fmap (\x -> (x, f x)) t)
partial i = fmap (\(k, (x, y)) -> if k < i then y else x) ti
in map partial [1..n]
Here, indexed operates in the state monad to add an incrementing index to elements of a traversable object (and gets the length "for free", whatever that means):
> indexed ['a','b','c']
([(0,'a'),(1,'b'),(2,'c')],3)
and, again, as Ben pointed out, it could also be written using mapAccumL:
indexed = swap . mapAccumL (\k x -> (k+1, (k, x))) 0
Then, scanMap takes the traversable object, fmaps it to a similar structure of before/after pairs, uses indexed to index it, and applies a sequence of partial functions, where partial i selects "afters" for the first i elements and "befores" for the rest.
> scanMap (*2) [1,2,3]
[[2,2,3],[2,4,3],[2,4,6]]
As for generalizing this from lists to something else, I can't figure out exactly what you're trying to do with your second signature:
func :: (Traversable t, Applicative f) => (a -> f a) -> t a -> f (t a)
because if you specialize this to a list you get:
func' :: (Traversable t) => (a -> [a]) -> t a -> [t a]
and it's not at all clear what you'd want this to do here.
On lists, I'd use the following. Feel free to discard the first element, if not wanted.
> let mymap f [] = [[]] ; mymap f ys#(x:xs) = ys : map (f x:) (mymap f xs)
> mymap (+1) [1,2,3]
[[1,2,3],[2,2,3],[2,3,3],[2,3,4]]
This can also work on Foldable, of course, after one uses toList to convert the foldable to a list. One might still want a better implementation that would avoid that step, though, especially if we want to preserve the original foldable type, and not just obtain a list.
I just called it func, per your question, because I couldn't think of a better name.
import Control.Monad.State
func f t = [evalState (traverse update t) n | n <- [0..length t - 1]]
where update x = do
n <- get
let y = if n == 0 then f x else x
put (n-1)
return y
The idea is that update counts down from n, and when it reaches 0 we apply f. We keep n in the state monad so that traverse can plumb n through as you walk across the traversable.
ghci> func (+1) [1,1,1]
[[2,1,1],[1,2,1],[1,1,2]]
You could probably save a few keystrokes using mapAccumL, a HOF which captures the pattern of traversing in the state monad.
This sounds a little like a zipper without a focus; maybe something like this:
data Zippy a b = Zippy { accum :: [b] -> [b], rest :: [a] }
mapZippy :: (a -> b) -> [a] -> [Zippy a b]
mapZippy f = go id where
go a [] = []
go a (x:xs) = Zippy b xs : go b xs where
b = a . (f x :)
instance (Show a, Show b) => Show (Zippy a b) where
show (Zippy xs ys) = show (xs [], ys)
mapZippy succ [1,2,3]
-- [([2],[2,3]),([2,3],[3]),([2,3,4],[])]
(using difference lists here for efficiency's sake)
To convert to a fold looks a little like a paramorphism:
para :: (a -> [a] -> b -> b) -> b -> [a] -> b
para f b [] = b
para f b (x:xs) = f x xs (para f b xs)
mapZippy :: (a -> b) -> [a] -> [Zippy a b]
mapZippy f xs = para g (const []) xs id where
g e zs r d = Zippy nd zs : r nd where
nd = d . (f e:)
For arbitrary traversals, there's a cool time-travelling state transformer called Tardis that lets you pass state forwards and backwards:
mapZippy :: Traversable t => (a -> b) -> t a -> t (Zippy a b)
mapZippy f = flip evalTardis ([],id) . traverse g where
g x = do
modifyBackwards (x:)
modifyForwards (. (f x:))
Zippy <$> getPast <*> getFuture

Recursion scheme in Haskell for repeatedly breaking datatypes into "head" and "tail" and yielding a structure of results

In Haskell, I recently found the following function useful:
listCase :: (a -> [a] -> b) -> [a] -> [b]
listCase f [] = []
listCase f (x:xs) = f x xs : listCase f xs
I used it to generate sliding windows of size 3 from a list, like this:
*Main> listCase (\_ -> take 3) [1..5]
[[2,3,4],[3,4,5],[4,5],[5],[]]
Is there a more general recursion scheme which captures this pattern? More specifically, that allows you to generate a some structure of results by repeatedly breaking data into a "head" and "tail"?
What you are asking for is a comonad. This may sound scarier than monad, but is a simpler concept (YMMV).
Comonads are Functors with additional structure:
class Functor w => Comonad w where
extract :: w a -> a
duplicate :: w a -> w (w a)
extend :: (w a -> b) -> w a -> w b
(extendand duplicate can be defined in terms of each other)
and laws similar to the monad laws:
duplicate . extract = id
duplicate . fmap extract = id
duplicate . duplicate = fmap duplicate . duplicate
Specifically, the signature (a -> [a] -> b) takes non-empty Lists of type a. The usual type [a] is not an instance of a comonad, but the non-empty lists are:
data NE a = T a | a :. NE a deriving Functor
instance Comonad NE where
extract (T x) = x
extract (x :. _) = x
duplicate z#(T _) = T z
duplicate z#(_ :. xs) = z :. duplicate xs
The comonad laws allow only this instance for non-empty lists (actually a second one).
Your function then becomes
extend (take 3 . drop 1 . toList)
Where toList :: NE a -> [a] is obvious.
This is worse than the original, but extend can be written as =>> which is simpler if applied repeatedly.
For further information, you may start at What is the Comonad typeclass in Haskell?.
This looks like a special case of a (jargon here but it can help with googling) paramorphism, a generalisation of primitive recursion to all initial algebras.
Reimplementing ListCase
Let's have a look at how to reimplement your function using such a combinator. First we define the notion of paramorphism: a recursion principle where not only the result of the recursive call is available but also the entire substructure this call was performed on:
The type of paraList tells me that in the (:) case, I will have access to the head, the tail and the value of the recursive call on the tail and that I need to provide a value for the base case.
module ListCase where
paraList :: (a -> [a] -> b -> b) -- cons
-> b -- nil
-> [a] -> b -- resulting function on lists
paraList c n [] = n
paraList c n (x : xs) = c x xs $ paraList c n xs
We can now give an alternative definition of listCase:
listCase' :: (a -> [a] -> b) -> [a] -> [b]
listCase' c = paraList (\ x xs tl -> c x xs : tl) []
Considering the general case
In the general case, we are interested in building a definition of paramorphism for all data structures defined as the fixpoint of a (strictly positive) functor. We use the traditional fixpoint operator:
newtype Fix f = Fix { unFix :: f (Fix f) }
This builds an inductive structure layer by layer. The layers have an f shape which maybe better grasped by recalling the definition of List using this formalism. A layer is either Nothing (we're done!) or Just (head, tail):
newtype ListF a as = ListF { unListF :: Maybe (a, as) }
type List a = Fix (ListF a)
nil :: List a
nil = Fix $ ListF $ Nothing
cons :: a -> List a -> List a
cons = curry $ Fix . ListF .Just
Now that we have this general framework, we can define para generically for all Fix f where f is a functor:
para :: Functor f => (f (Fix f, b) -> b) -> Fix f -> b
para alg = alg . fmap (\ rec -> (rec, para alg rec)) . unFix
Of course, ListF a is a functor. Meaning we could use para to reimplement paraList and listCase.
instance Functor (ListF a) where fmap f = ListF . fmap (fmap f) . unListF
paraList' :: (a -> List a -> b -> b) -> b -> List a -> b
paraList' c n = para $ maybe n (\ (a, (as, b)) -> c a as b) . unListF
listCase'' :: (a -> List a -> b) -> List a -> List b
listCase'' c = paraList' (\ x xs tl -> cons (c x xs) tl) nil
You can implement a simple bijection toList, fromList to test it if you want. I could not be bothered to reimplement take so it's pretty ugly:
toList :: [a] -> List a
toList = foldr cons nil
fromList :: List a -> [a]
fromList = paraList' (\ x _ tl -> x : tl) []
*ListCase> fmap fromList . fromList . listCase'' (\ _ as -> toList $ take 3 $ fromList as). toList $ [1..5]
[[2,3,4],[3,4,5],[4,5],[5],[]]

How to remove an item from a list by index using the lens library?

I can view the, say, 4th item in a list using a lens like this:
preview (ix 3) myList
Is there something that could replace "preview" in order to remove the fourth item from the list instead of viewing it? The return list should be the same as the original list say the 4th item would be deleted.
Or perhaps there may be a way of doing this using the filtered function?
Sounds like you want to use ifiltered:
toListOf (folded . ifiltered (\i _ -> i /= 3)) $ myList
-- or
myList ^.. folded . ifiltered (\i _ -> i /= 3))
There is a more general way of doing this, using Monoid and Foldable.
deleteN
:: (Foldable f, Monoid (f a))
=> (a -> f a -> f a) -- ^ cons operator
-> Int -- ^ index to delete
-> f a -- ^ initial structure
-> f a -- ^ resultant structure
deleteN cons n xs = flipTfo xs $ folded . ifiltered (\i _ -> i /= n)
where
flipTfo = flip toFoldableOf
toFoldableOf l = foldrOf l cons mempty
and you can specialise this to list with
deleteList :: Monoid a => Int -> [a] -> [a]
deleteList = deleteN (:)

Adding predicate to a map function

Completely new to Haskell and learning through Learn Haskell the greater good.
I am looking at the map function
map :: (a -> b) -> [a] -> [b]
map _ [] = []
map f (x:xs) = f x : map f xs
is it possible to add a predicate to this? for example, to only map to every other element in the list?
You can code your own version of map to apply f only to even (or odd) positions as follows. (Below indices start from 0)
mapEven :: (a->a) -> [a] -> [a]
mapEven f [] = []
mapEven f (x:xs) = f x : mapOdd f xs
mapOdd :: (a->a) -> [a] -> [a]
mapOdd f [] = []
mapOdd f (x:xs) = x : mapEven f xs
If instead you want to exploit the library functions, you can do something like
mapEven :: (a->a) -> [a] -> [a]
mapEven f = map (\(flag,x) -> if flag then f x else x) . zip (cycle [True,False])
or even
mapEven :: (a->a) -> [a] -> [a]
mapEven f = map (uncurry (\flag -> if flag then f else id)) . zip (cycle [True,False])
If you want to filter using an arbitrary predicate on the index, then:
mapPred :: (Int -> Bool) -> (a->a) -> [a] -> [a]
mapPred p f = map (\(i,x) -> if p i then f x else x) . zip [0..]
A more direct solution can be reached using zipWith (as #amalloy suggests).
mapEven :: (a->a) -> [a] -> [a]
mapEven f = zipWith (\flag x -> if flag then f x else x) (cycle [True,False])
This can be further refined as follows
mapEven :: (a->a) -> [a] -> [a]
mapEven f = zipWith ($) (cycle [f,id])
The "canonical" way to perform filtering based on positions is to zip the sequence with the naturals, so as to append an index to each element:
> zip [1, 1, 2, 3, 5, 8, 13] [0..]
[(1,0),(1,1),(2,2),(3,3),(5,4),(8,5),(13,6)]
This way you can filter the whole thing using the second part of the tuples, and then map a function which discards the indices:
indexedFilterMap p f xs = (map (\(x,_) -> f x)) . (filter (\(_,y) -> p y)) $ (zip xs [0..])
oddFibsPlusOne = indexedFilterMap odd (+1) [1, 1, 2, 3, 5, 8, 13]
To be specific to you question, one might simply put
mapEveryOther f = indexedFilterMap odd f
You can map with a function (a lambda is also possible):
plusIfOdd :: Int -> Int
plusIfOdd a
| odd a = a
| otherwise = a + 100
map plusIfOdd [1..5]
As a first step, write the function for what you want to do to the individual element of the list:
applytoOdd :: Integral a => (a -> a) -> a -> a
applytoOdd f x = if odd x
then (f x)
else x
So applytoOdd function will apply the function f to the element if the element is odd or else return the same element if it is even. Now you can apply map to that like this:
λ> let a = [1,2,3,4,5]
λ> map (applytoOdd (+ 100)) a
[101,2,103,4,105]
Or if you want to add 200 to it, then:
λ> map (applytoOdd (+ 200)) a
[201,2,203,4,205]
Looking on the comments, it seems you want to map based on the index position. You can modify your applytoOdd method appropriately for that:
applytoOdd :: Integral a => (b -> b) -> (a, b) -> b
applytoOdd f (x,y) = if odd x
then (f y)
else y
Here, the type variable a corresponds to the index element. If it's odd you are applying the function to the actual element of the list. And then in ghci:
λ> map (applytoOdd (+ 100)) (zip [1..5] [1..])
[101,2,103,4,105]
λ> map (applytoOdd (+ 200)) (zip [1..5] [1..])
[201,2,203,4,205]
Or use a list comprehension:
mapOdd f x = if odd x then f x else x
[ mapOdd (+100) x | x <- [1,2,3,4,5]]
I'm glad that you're taking the time to learn about Haskell. It's an amazing language. However it does require you to develop a certain mindset. So here's what I do when I face a problem in Haskell. Let's start with your problem statement:
Is it possible to add a predicate to the map function? For example, to only map to every other element in the list?
So you have two questions:
Is it possible to add a predicate to the map function?
How to map to every other element in the list?
So the way people think in Haskell is via type signatures. For example, when an engineer is designing a building she visualizes how the building should look for the top (top view), the front (front view) and the side (side view). Similarly when functional programmers write code they visualize their code in terms of type signatures.
Let's start with what we know (i.e. the type signature of the map function):
map :: (a -> b) -> [a] -> [b]
Now you want to add a predicate to the map function. A predicate is a function of the type a -> Bool. Hence a map function with a predicate will be of the type:
mapP :: (a -> Bool) -> (a -> b) -> [a] -> [b]
However, in your case, you also want to keep the unmapped values. For example mapP odd (+100) [1,2,3,4,5] should result in [101,2,103,4,105] and not [101,103,105]. Hence it follows that the type of the input list should match the type of the output list (i.e. a and b must be of the same type). Hence mapP should be of the type:
mapP :: (a -> Bool) -> (a -> a) -> [a] -> [a]
It's easy to implement a function like this:
map :: (a -> Bool) -> (a -> a) -> [a] -> [a]
mapP p f = map (\x -> if p x then f x else x)
Now to answer your second question (i.e. how to map to every other element in the list). You could use zip and unzip as follows:
snd . unzip . mapP (odd . fst) (fmap (+100)) $ zip [1..] [1,2,3,4,5]
Here's what's happening:
We first zip the index of each element with the element itself. Hence zip [1..] [1,2,3,4,5] results in [(1,1),(2,2),(3,3),(4,4),(5,5)] where the fst value of each pair is the index.
For every odd index element we apply the (+100) function to the element. Hence the resulting list is [(1,101),(2,2),(3,103),(4,4),(5,105)].
We unzip the list resulting in two separate lists ([1,2,3,4,5],[101,2,103,4,105]).
We discard the list of indices and keep the list of mapped results using snd.
We can make this function more general. The type signature of the resulting function would be:
mapI :: ((Int, a) -> Bool) -> (a -> a) -> [a] -> [a]
The definition of the mapI function is simple enough:
mapI :: ((Int, a) -> Bool) -> (a -> a) -> [a] -> [a]
mapI p f = snd . unzip . mapP p (fmap f) . zip [1..]
You can use it as follows:
mapI (odd . fst) (+100) [1,2,3,4,5]
Hope that helps.
Is it possible to add a predicate to this? for example, to only map to every other element in the list?
Yes, but functions should ideally do one relatively simple thing only. If you need to do something more complicated, ideally you should try doing it by composing two or more functions.
I'm not 100% sure I understand your question, so I'll show a few examples. First: if what you mean is that you only want to map in cases where a supplied predicate returns true of the input element, but otherwise just leave it alone, then you can do that by reusing the map function:
mapIfTrue :: (a -> Bool) -> (a -> a) -> [a] -> [a]
mapIfTrue pred f xs = map step xs
where step x | pred x = f x
| otherwise = x
If what you mean is that you want to discard list elements that don't satisfy the predicate, and apply the function to the remaining ones, then you can do that by combining map and filter:
filterMap :: (a -> Bool) -> (a -> b) -> [a] -> [b]
filterMap pred f xs = map f (filter pred xs)
Mapping the function over every other element of the list is different from these two, because it's not a predicate over the elements of the list; it's either a structural transformation of the list of a stateful traversal of it.
Also, I'm not clear whether you mean to discard or keep the elements you're not applying the function to, which would imply different answers. If you're discarding them, then you can do it by just discarding alternate list elements and then mapping the function over the remaining ones:
keepEven :: [a] -> [a]
keepEven xs = step True xs
where step _ [] = []
step True (x:xs) = x : step False xs
step False (_:xs) = step True xs
mapEven :: (a -> b) -> [a] -> [b]
mapEven f xs = map f (keepEven xs)
If you're keeping them, one way you could do it is by tagging each list element with its position, filtering the list to keep only the ones in even positions, discard the tags and then map the function:
-- Note: I'm calling the first element of a list index 0, and thus even.
mapEven :: (a -> a) -> [a] -> [a]
mapEven f xs = map aux (filter evenIndex (zip [0..] xs))
where evenIndex (i, _) = even i
aux (_, x) = f x
As another answer mentioned, zip :: [a] -> [b] -> [(a, b)] combines two lists pairwise by position.
But this is the general philosophy: to do a complex thing, use a combination of general-purpose generic functions. If you're familiar with Unix, it's similar to that.
Another simple way to write the last one. It's longer, but keep in mind that evens, odds and interleave all are generic and reusable:
evens, odds :: [a] -> [a]
evens = alternate True
odds = alternate False
alternate :: Bool -> [a] -> [a]
alternate _ [] = []
alternate True (x:xs) = x : alternate False xs
alternate False (_:xs) = alternate True xs
interleave :: [a] -> [a] -> [a]
interleave [] ys = ys
interleave (x:xs) ys = x : interleave ys xs
mapEven :: (a -> a) -> [a] -> [a]
mapEven f xs = interleave (map f (evens xs)) (odds xs)
You can't use a predicate because predicates operate on list values, not their indices.
I quite like this format for what you're trying to do, since it makes the case handling quite clear for the function:
newMap :: (t -> t) -> [t] -> [t]
newMap f [] = [] -- no items in list
newMap f [x] = [f x] -- one item in list
newMap f (x:y:xs) = (f x) : y : newMap f xs -- 2 or more items in list
For example, running:
newMap (\x -> x + 1) [1,2,3,4]
Yields:
[2,2,4,4]

Resources