osobennyj
osobennyj

Reputation: 75

Map function applied to specific elements of the list

I have a function:

mapAtOriginal :: (a -> a) -> [Int] -> [a] -> [a]
mapAtOriginal f is xs = helper 0 is xs
  where
    helper _ [] xs = xs
    helper c (i:is) (x:xs)
      | c < i     =   x : helper (c+1) (i:is) xs
      | otherwise = f x : helper (c+1)    is  xs

It works like this:

mapAtOriginal (*2) [0,3] [1,2,3,4]   -- == [2,2,3,8]

So I want to rewrite it but using a map function. I understand that map applies to every element of the list, however, I need it applied only for specific indices.

How can I do it?

Upvotes: 1

Views: 1018

Answers (3)

Will Ness
Will Ness

Reputation: 71119

Starting from the idea from jpmarinier's answer of filling up the empty spaces in the indices list; using package data-ordlist,

{-# LANGUAGE TupleSections #-}

import qualified Data.List.Ordered    as   O
import           Data.Ord  (comparing)

mapAtOriginal :: (a -> a) -> [Int] -> [a] -> [a]
mapAtOriginal f is xs = 
  zipWith (flip ($))                        -- apply zippily
    xs
    (map fst $                              -- recover the functions, `f` or `id`
          O.unionBy (comparing snd)         -- `is` is assumed subset of [0..]
                    (map (f  ,) is   )      -- tag with
                    (map (id ,) [0..]) )    --      indices

It's like getZipList $ (f `_at` is) `_or` (id `_at` [0..]) <*> ZipList xs with some ad-hoc definitions for _at and _or.

This uses the fact that data-ordlist's union is left-biased, i.e. it picks the elements from its first argument list over those from its second, on collisions.

Upvotes: 2

jpmarinier
jpmarinier

Reputation: 4733

If you insist on using map to solve this problem, a possible route consists in making use of an auxiliary list of type [(a, Bool)], where only the indexed elements are paired with a True boolean value.

The function producing this auxiliary list could be declared like this:

markIndexedElements :: [Int] -> [a] -> [(a, Bool)]

If we have such a function, the rest of our problem becomes easy:

 λ> auxList = markIndexedElements [0,3] [1,2,3,4]
 λ> auxList
 [(1,True),(2,False),(3,False),(4,True)]
 λ> 
 λ> map  (\(x, b) -> if b then (2*x) else x)  auxList
 [2,2,3,8]
 λ> 

The markIndexedElements function makes a second list out of the first list, while maintaining some state information. So if we prefer a ready-made recursion scheme, it seems to be a job for the scanl :: (b -> a -> b) -> b -> [a] -> [b] function.

The state to be maintained consists mostly of the current position in the original list plus the list of so far unused indices. If the current position is equal to the next index, we drop that index and output an (x, True) pair. This gives the following code:

-- only indexed elements to get paired with a True value
markIndexedElements :: [Int] -> [a] -> [(a, Bool)]
markIndexedElements indices xs =
    let  sfn ((_,p),(pos,ind)) y =  -- stepping function for scanl
             if (null ind)
               then ((y, False), (pos+1,[]))
               else ((y, pos==head ind),
                     (pos+1, if (pos==head ind)  then  tail ind  else  ind))
         scanRes = scanl  sfn  ((undefined,False), (0,indices))  xs
    in   map fst  $  drop 1 scanRes

The rest of the code is not difficult to write:

mapAtOriginal :: (a -> a) -> [Int] -> [a] -> [a]
mapAtOriginal fn indices xs =
    let  pairList  = markIndexedElements indices xs   -- auxiliary list
         pfn (x,b) = if b then (fn x) else x          -- auxiliary function
    in   map pfn pairList


main = do
    let  xs      = [1,2,3,4]
         indices = [0,3]
         result  = mapAtOriginal (*2) indices xs
    putStrLn $ show (markIndexedElements indices xs)
    putStrLn $ show result

Program output:

[(1,True),(2,False),(3,False),(4,True)]
[2,2,3,8]

Similar solutions:

If we try to apply just one more step of Cartesian reductionism to this problem, we can note that argument xs plays only a minor role in the markIndexedElements function. A possibility is to eliminate it completely, and have instead a function that returns just an unlimited list of boolean values:

booleansFromIndices :: [Int] -> [Bool]
booleansFromIndices indices =
    let  sfn (pos,ind) =  Just $  -- stepping function for unfoldr
             if (null ind)
               then ( False, (pos+1, []) )
               else ( pos==head ind,
                      (pos+1, if (pos==head ind)  then  tail ind  else  ind))
    in   unfoldr  sfn  (0,indices)

The resulting list ends with an unlimited sequence of False values after the last index:

 λ> take 10 $ booleansFromIndices [0,3]
 [True,False,False,True,False,False,False,False,False,False]
 λ> 

The target mapAtOriginal function can then be rewritten using booleansFromIndices:

mapAtOriginal :: (a -> a) -> [Int] -> [a] -> [a]
mapAtOriginal fn indices xs =
    let  pairList   = zip xs $ booleansFromIndices indices
         pfn (x, b) = if b  then  (fn x)  else  x
    in   map pfn pairList

Last but not least, as already noted by other answerers/commenters, the map+zip scheme can generally be replaced by one based on the zipWith function. Like this, in our case:

mapAtOriginal :: (a -> a) -> [Int] -> [a] -> [a]
mapAtOriginal fn indices xs =
    let  booleans = booleansFromIndices indices
    in   zipWith  (\x b -> if b  then  (fn x)  else  x)  xs  booleans

Upvotes: 2

leftaroundabout
leftaroundabout

Reputation: 120751

map doesn't know “where in the list” it is. So you first need to encode that information into the elements themselves. This can be done with zip [0..], which basically annotates each element with position at which it occurs.

Then, in the function you map, you just need to pattern-match on the annotation-tuple, and use an if to decide whether or not to apply the manipulator function to the other tuple element.

Note that the combination of zip and map is always equivalent to a single pass zipWith, so that's what you should preferrably use.

Upvotes: 4

Related Questions