Replace elements in the list - haskell

I need to implement a function that replaces elements in a list -- the
index to replace at is the fst in the tuple, and the snd in the tuple
is what to replace it with. and I am asked to use foldr or map function.
for example:
setElements [(1, 'a'), (-4, 't'), (3, 'b')] "#####" = "#a#b#"
the setElements function doesn't compile:
my code:
setElement :: Int -> a -> [a] -> [a]
setElement n x xs = if ((n < length xs) && n >= 0)
then (take n xs) ++ [x] ++ (drop (n + 1) xs)
else xs
setElements :: [(Int, a)] -> [a] -> [a]
setElements = foldr (\t l-> setElement (fst t) (snd t) l) []
I get:
• Couldn't match type ‘[a]’ with ‘[a] -> [a]’
Expected type: [(Int, a)] -> [a] -> [a]
Actual type: [(Int, a)] -> [a]
• Possible cause: ‘foldr’ is applied to too many arguments
In the expression: foldr (\ t l -> setElement (fst t) (snd t) l) []
In an equation for ‘setElements’:
setElements = foldr (\ t l -> setElement (fst t) (snd t) l) []
• Relevant bindings include
setElements :: [(Int, a)] -> [a] -> [a]
(bound at hw3.hs:79:1)
|
79 | setElements = foldr (\t l-> setElement (fst t) (snd t) l) []
|
How can I fix the error?

Let's look at your function:
setElements :: [(Int, a)] -> [a] -> [a]
setElements = foldr (\t l-> setElement (fst t) (snd t) l) []
and recall the type of foldr:
foldr :: (a -> b -> b) -> b -> [a] -> b
In your use of foldr, you have a as (Int, a) and b as [a]. And you only give it the first 2 arguments. So foldr (\t l-> setElement (fst t) (snd t) l) [] has type [(Int, a)] -> [a] - whereas setElements is supposed to have type [(Int, a)] -> [a] -> [a]. Note how these match exactly with the "actual type" and "expected type" reported by GHC in the error message.
To fix this, I would actually take a step backwards. Folding is the right idea - your setElement function already modifies the original list (its third argument) based on an index and new value, and what you want is to take a list of pairs encoding this data, and keep on applying this function to update the original list repeatedly. (Of course this is Haskell so data is immutable - you're not literally updating it in place, but simply returning a new list each time. But sometimes talking loosely like this is easier.)
That's exactly what a fold is. Let's try to write it out, without trying to be too fancy with a "point-free" approach, but instead fully applying it:
setElements :: [(Int, a)] -> [a] -> [a]
setElements ps as = foldr myFunction as ps
where myFunction = undefined
The undefined here is just a placeholder - it will cause a runtime error if you try to use the function (but won't cause a compilation error), and I've put it there because we need to think about that, the fold function usually being the trickiest part of implementing a fold. But let's check we understand what the other terms are doing: the list we are actually "walking along" is the list of (Int, a) terms that tell us what to insert and where - that's what I've called ps (the p is for "pair"). And because we are starting with the list of as - which I've logically called as here - then that should be the starting accumulator value, which is the second argument to foldr.
So all that remains is the fold function - which takes a pair and a list, and updates the list according to the values in the pair. Well this is the function you're already using:
\t l-> setElement (fst t) (snd t) l
or, rewritten with pattern matching (which I find much more readable, and for this reason I think is preferred by most Haskell developers):
\(i, a) as -> setElement i a as
So, substituting this in, we arrive at the following definition:
setElements :: [(Int, a)] -> [a] -> [a]
setElements ps as = foldr myFunction as ps
where myFunction = \(i, a) as -> setElement i a as
This now will compile and work correctly. But it's always worth taking a step back when you have a working function, and seeing if you can simplify its definition. In fact myFunction can be simplified quite a bit:
\(i, a) as -> setElement i a as
can first be "eta-reduced" to
\(i, a) -> setElement i a
which, using a standard library function, is simply uncurry setElement.
At this stage we clearly don't need a where clause any more (in fact we never did before, but imo it aids readability for any lambda which isn't fairly trivial), and can just write:
setElements :: [(Int, a)] -> [a] -> [a]
setElements ps as = foldr (uncurry setElement) as ps
In fact, while I wouldn't necessarily recommend it, if we're playing code golf you can even go a step further and just write:
setElements = flip . foldr . uncurry $ setElement
I personally think the ability to be able to express relatively complex functions in a concise way, as above, is definitely part of the allure of Haskell. But, rather than try to write something like this straight away, in my opinion it's always best to start with something very concrete showing how you want to transform your data - and, only after getting that working, look for a more concise representation if you want to.

Related

Remove first element that fulfills predicate (Haskell)

I want to make a function that removes the first element that fulfills the predicate given in the second argument. Something like this:
removeFirst "abab" (< 'b') = "bab"
removeFirst "abab" (== 'b') = "aab"
removeFirst "abab" (> 'b') = "abab"
removeFirst [1,2,3,4] even = [1,3,4]
I wanted to do it by recursively, and came up with this:
removeFirst :: [a] -> (a -> Bool) -> [a]
removeFirst [] _ = []
rremoveFirst (x:xs) p = if p x then x : removeFirst xs p else removeFirst xs p
(Inspired by this question)
But I get a type-error, like this:
Couldn't match type ‘a’ with ‘Bool’
Expected: [Bool]
Actual: [a]
‘a’ is a rigid type variable bound by
the type signature for:
removeFirst :: forall a. [a] -> (a -> Bool) -> [a]
or this:
ghci> removeFirst [1,2,3,4] even
<interactive>:25:1: error:
* Variable not in scope: removeFirst :: [a0] -> (a1 -> Bool) -> t
* Perhaps you meant `rem' (imported from Prelude)
I know this is a relatively simple thing to program, I am just not familiar enough with Haskell yet. How can I do this "Haskell-style" (in one line)?
Before doing it "in style", why not first simply do it, so it works. This is how we learn.
"Variable not in scope: removeFirst ..." simply means you haven't defined the function named removeFirst.
So it seems you first tried to define it (and the error you show does not go with the code you show), then you got errors so it didn't get defined, and then you tried calling it and got the error saying it's not defined yet, naturally.
So, save your program in a source file, then load that file in GHCi. Then if you get any errors please copy-paste the full code from your file into your question (do not re-type it by hand). Also please specify what is it you do when you get the error messages, precisely. And be sure to include the error messages in full by copy-pasting them as well.
Then the logic of your code can be addressed.
Since others have posted working code, here's how I'd code this as a one-liner of sorts:
remFirst :: [a] -> (a -> Bool) -> [a]
remFirst xs p = foldr g z xs xs
where
g x r ~(_:tl) -- "r" for recursive result
| p x -- we've found it, then
= tl -- just return the tail
| otherwise
= x : r tl -- keep x and continue
z _ = [] -- none were found
Shortened, it becomes
remFirst xs p =
foldr (\x r ~(_:tl) -> if p x then tl else x : r tl)
(const []) xs xs
Not one line, but it works.
removeFirst :: [a] -> (a -> Bool) -> [a]
removeFirst (x:xs) pred
| pred x = xs
| otherwise = x : removeFirst xs pred
For a one-liner, I imagine you'd want to use foldl to walk across the list from the left.
EDIT
This solution uses guards, it first checks to see if the first element of the list passed in satisfies the predicate, and if not, it prepends it to the list and recursively checks the tail of the passed in list.
Using manual recursion does not lead to a one-liner solution, so let's try using some pre-built recursion scheme from the library.
Function scanl :: (b -> a -> b) -> b -> [a] -> [b] looks handy. It produces a succession of states, one state per input item.
Testing under the ghci interpreter:
$ ghci
λ>
λ> p = (=='b')
λ>
λ> xs = "ababcdab"
λ> ss = tail $ scanl (\(s,n) x -> if (p x) then (x,n+1) else (x,n)) (undefined,0) xs
λ>
λ> ss
[('a',0),('b',1),('a',1),('b',2),('c',2),('d',2),('a',2),('b',3)]
λ>
At that point, it is easy to spot and get rid of the one unwanted element, thru some simple data massaging:
λ>
λ> filter (\(x,n) -> (n /= 1) || (not $ p x)) ss
[('a',0),('a',1),('b',2),('c',2),('d',2),('a',2),('b',3)]
λ>
λ> map fst $ filter (\(x,n) -> (n /= 1) || (not $ p x)) ss
"aabcdab"
λ>
Let's now write our removeFirst function. I take the liberty to have the predicate as leftmost argument; this is what all library functions do.
removeFirst :: (a -> Bool) -> [a] -> [a]
removeFirst p =
let
stepFn = \(s,n) x -> if (p x) then (x,n+1) else (x,n)
p2 = \(x,n) -> (n /= 1) || (not $ p x)
in
map fst . filter p2 . tail . scanl stepFn (undefined,0)
If required, this version can be changed into a one-liner solution, just by expanding the values of stepFn and p2 into the last line. Left as an exercise for the reader. It makes for a long line, so it is debatable whether that improves readability.
Addendum:
Another approach consists in trying to find a library function, similar to splitAt :: Int -> [a] -> ([a], [a]) but taking a predicate instead of the list position.
So we submit the (a -> Bool) -> [a] -> ([a],[a]) type signature into the Hoogle specialized search engine.
This readily finds the break library function. It is exactly what we require.
λ>
λ> break (=='b') "zqababcdefab"
("zqa","babcdefab")
λ>
So we can write our removeFirst function like this:
removeFirst :: (a -> Bool) -> [a] -> [a]
removeFirst p xs = let (ys,zs) = break p xs in ys ++ (tail zs)
The source code for break simply uses manual recursion.

Rotate function in Haskell

I want to write a function in Haskell that rotates the list given as the second argument by the number of positions indicated by the first argument. Using pattern matching, implement a recursive function
I have written the following function:
rotate :: Int -> [a] -> [a]
rotate 0 [y]= [y]
rotate x [y]= rotate((x-1) [tail [y] ++ head [y]])
but this function always produces a error. Is there any way to solve it?
The function should do the following when it runs:
rotate 1 "abcdef"
"bcdefa"
[y] does not mean "let y be a list". It means "this argument is a list containing one element called y". You have the right structure, but you don't need the brackets around the y.
rotate :: Int -> [a] -> [a]
rotate 0 y = y
rotate x y = rotate (x-1) (tail y ++ [head y])
TL&DR
rotate :: Int -> [a] -> [a]
rotate = drop <> take
In Haskell the most concise but also a curious way to rotate a list could be using the Semigroup type class instance of the function type (a -> b). Lets check the relevant part of the instance.
instance Semigroup b => Semigroup (a -> b) where
f <> g = \x -> f x <> g x
First things first, <> is in fact the inline version of the mappend function from the Monoid type class.
Then we see, the Semigroup b => constraint in the type signature states that the return type b should also be a member of Semigroup type class. Since we use drop :: Int -> [a] -> [a] and take :: Int -> [a] -> [a] we can quickly notice that b is in fact another function with type signature [a] -> [a] so it is a member of Semigroup type class if and only if it's b, which happens to be [a] is also a member of the Semigroup type class and it is.
instance Semigroup [a] where
(<>) = (++)
So everything holds so far but how does it work?
We can deduce from the type signatures as follows;
(drop :: Int -> ([a] -> [a])) <> (take :: Int -> ([a] -> [a])) is
\n -> (drop n :: [a] -> [a]) <> (take n :: [a] -> [a]) which is
\n -> \xs -> (drop n xs :: [a]) <> (take n xs :: [a]) which is
\n -> \xs -> (drop n xs) ++ (take n xs)
This is basically better than the answers using recursive ++ operator to add the head as a singleton list to the end of the tail since it yields an O(n^2) time complexity.
I think you want something like this:
rotate :: Int -> [a] -> [a]
rotate 0 x = x
rotate times (x:xs) = rotate (times - 1) (xs ++ [x])

Converting a foldl into fold1

I am using the following fold to get the final monotonically decreasing sequence of a list.
foldl (\acc x -> if x<=(last acc) then acc ++ [x] else [x]) [(-1)] a
So [9,5,3,6,2,1] would return [6,2,1]
However, with foldl I needed to supply a start for the fold namely [(-1)]. I was trying to turn into to a foldl1 to be able to handle any range of integers as well as any Ord a like so:
foldl1 (\acc x -> if x<=(last acc) then acc ++ [x] else [x]) a
But I get there error:
cannot construct infinite type: a ~ [a]
in the second argument of (<=) namely last acc
I was under the impression that foldl1 was basically :
foldl (function) [head a] a
But I guess this isn't so? How would you go about making this fold generic for any Ord type?
I was under the impression that foldl1 was basically :
foldl (function) [head a] a
No, foldl1 is basically:
foldl function (head a) (tail a)
So the initial element is not a list of head a, but head a.
How would you go about making this fold generic for any Ord type?
Well a quick fix is:
foldl (\acc x -> if x<=(last acc) then acc ++ [x] else [x]) [head a] (tail a)
But there are still two problems:
in case a is an empty list, this function will error (while you probably want to return the empty list); and
the code is not terribly efficient since both last and (++) run in O(n).
The first problem can easily be addressed by using pattern matching to prevent that scenario. But for the latter you better would for instance use a reverse approach. Like for instance:
f :: Ord t => [t] -> [t]
f [] = [] -- case when the empty list is given
f a = reverse $ foldl (\acc#(ac:_) x -> if x <= ac then (x:acc) else [x]) [head a] (tail a)
Furthermore personally I am not a huge fan of if-then-else in functional programming, you can for instance define a helper function like:
f :: Ord t => [t] -> [t]
f [] = [] -- case when the empty list is given
f a = reverse $ foldl g [head a] (tail a)
where g acc#(ac:_) x | x <= ac = (x:acc)
| otherwise = [x]
Now reverse runs in O(n) but this is done only once. Furthermore the (:) construction runs in O(1) so all the actions in g run in O(1) (well given the comparison of course works efficient, etc.) making the algorithm itself O(n).
For your sample input it gives:
*Main> f [9,5,3,6,2,1]
[6,2,1]
The type of foldl1 is:
Foldable t => (a -> a -> a) -> t a -> a
Your function argument,
\acc x -> if x<=(last acc) then acc ++ [x] else [x]
has type:
(Ord a) => [a] -> a -> [a]
When Haskell's typechecker tries typechecking your function, it'll try unifying the type a -> a -> a (the type of the first argument of foldl1) with the type [a] -> a -> [a] (the type of your function).
To unify these types would require unifying a with [a], which would lead to the infinite type a ~ [a] ~ [[a]] ~ [[[a]]]... and so on.
The reason this works while using foldl is that the type of foldl is:
Foldable t => (b -> a -> b) -> b -> t a -> b
So [a] gets unified with b and a gets unified with the other a, leading to no problem at all.
foldl1 is limited in that it can only take functions which deal with only one type, or, in other terms, the accumulator needs to be the same type as the input list (for instance, when folding a list of Ints, foldl1 can only return an Int, while foldl can use arbitrary accumulators. So you can't do this using foldl1).
With regards to making this generic for all Ord values, one possible solution is to make a new typeclass for values which state their own "least-bound" value, which would then be used by your function. You can't make this function as it is generic on all Ord values because not all Ord values have sequence least bounds you can use.
class LowerBounded a where
lowerBound :: a
instance LowerBounded Int where
lowerBound = -1
finalDecreasingSequence :: (Ord a, LowerBounded a) => [a] -> [a]
finalDecreasingSequence = foldl buildSequence lowerBound
where buildSequence acc x
| x <= (last acc) = acc ++ [x]
| otherwise = [x]
You might also want to read a bit about how Haskell does its type inference, as it helps a lot in figuring out errors like the one you got.

Is there any function in Haskell that applies a two argument function to two lists, element by element?

I just wanted to multiply two lists element by element, so I'd pass (*) as the first argument to that function:
apply :: Num a => (a -> a -> a) -> [a] -> [a] -> [a]
apply f xs ys = [f (xs !! i) (ys !! i) | i <- [0..(length xs - 1)]]
I may be asking a silly question, but I actually googled a lot for it and just couldn't find. Thank you, guys!
> :t zipWith
zipWith :: (a -> b -> c) -> [a] -> [b] -> [c]
> zipWith (*) [1,2,3] [4,5,6]
[4,10,18]
It's the eighth result provided by Hoogle when queried with your type
(a -> a -> a) -> [a] -> [a] -> [a]
Moreover, when you need to implement your own function, use list !! index only as a last resort, since it usually leads to a bad performance, having a cost of O(index). Similarly, length should be used only when necessary, since it needs to scan the whole list.
In the zipWith case, you can avoid both and proceed recursively in a natural way: it is roughly implemented as
zipWith _ [] _ = []
zipWith _ _ [] = []
zipWith f (x:xs) (y:ys) = f x y : zipWith f xs ys
Note that this will only recurse as much as needed to reach the end of the shortest list. The remaining part of the longer list will be discarded.

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