[Haskell-beginners] cleanest way to unwrap a list?

Nick Vanderweit nick.vanderweit at gmail.com
Wed Aug 15 01:02:33 CEST 2012


Try to exploit the repeated structure of the list. Here is an implementation 
of your "modify" function which does this.


modifyAt :: Int -> (a -> a) -> [a] -> [a]
modifyAt n f xs = let (inits, (e:tails)) = splitAt n xs
                    in inits ++ (f e):tails

modify :: [[a]] -> Int -> Int -> (a -> a) -> [[a]]
modify mat x y f = modifyAt y (modifyAt x f) mat


Nick


On Tuesday, August 14, 2012 10:50:42 PM Carlos J. G. Duarte wrote:
> I know it's doable. I was asking if there's a practical / elegant  way to do
> it. I see a lot of Haskell elegance when the matter is defining math
> formulas, running functions over elements, and so on. But it seems most of
> that elegance goes away when the problem derails a bit.
> 
> Now for my problem I come up with this:
> modify mat x y f =
>   let (lrows, row, rrows) = getpart mat x
>       (lcols, col, rcols) = getpart row y
>   in lrows ++ [lcols ++ [f col] ++ rcols] ++ rrows
>   where
>     getpart xs x = let (ls, r:rs) = splitAt x xs in (ls, r, rs)
> 
> m0 = [[1,2,3], [4,5,6], [7,8,9]]
> 
> main = do
>   print m0
>   let m1 = modify m0 1 1 succ
>   let m2 = modify m1 2 0 pred
>   print m2
> Which is a bit "awkward" considering the ease it is done in other languages.
> 
> On 08/14/12 19:35, Tim Perry wrote:
> There is a way. Please try to figure it out and if you fail post back with
> your code and we can help you from there.
> 
> 
> 
> On Tue, Aug 14, 2012 at 11:05 AM, Carlos J. G. Duarte
> <carlos.j.g.duarte at gmail.com> wrote: Ok, you all have been showing examples
> of running functions over elements. Add one, append value, and so on. This
> works well if there's one or more operations to apply indistinctly to a
> number of elements.
> 
> Now, what if we just want to make a single operation to a single element?
> For example, let's say I have this square matrix
> [[1,2,3],
>  [4,5,6],
>  [7,8,9]]
> 
> how can we increment the value 5 (position 2,2) *and* decrement the value 7
> (position 3,1)?
> 
> This is a made up example of course, I just want to see / learn if there's a
> way to apply a function to a specific subset of elements.
> 
> 
> On 08/14/12 00:06, Jack Henahan wrote:
> Equally,
> 
>      let map' = map . map
>      map' (+1) . map (++[3]) $ [[1,2],[3,4]]
>      -- [[2,3,4],[4,5,4]]
> 
> And you can really keep stacking those up. I think this approach will be
> cleaner in the long run.
> 
> For instance, let's start naming our parts.
>         let list = [[1,2],[3,4]]
>     let map' = map . map
>     let addOne = map' (+1)
>     let appendThree = map (++[3])
>     let reverseInner = map reverse
> 
> So, from here we can do the following:
>         list
>     -- [[1,2],[3,4]]
> 
>     -- the first example
>     addOne list
>     -- [[2,3],[4,5]]
>         -- now the second example
>     addOne . appendThree $ list
>     -- [[2,3,4],[4,5,4]]
> 
>     -- now add one to all members of the list, append three to the list,
> reverse the inner lists, -- then add one to all members of the new list
> 
>     addOne . reverseInner . appendThree . addOne $ list
>     -- [[4,4,3],[4,6,5]]
> 
> Now how would you construct that as a list comprehension? With the method
> I've proposed, you need only use map to operate on the nested lists
> themselves and map' to operate on the elements of those lists.
> 
> ====
> Jack Henahan
> jhenahan at uvm.edu
>        
> On Aug 13, 2012, at 6:41 PM, Christopher Howard
> <christopher.howard at frigidcode.com> wrote:
> 
> On 08/12/2012 09:37 PM, Shakthi Kannan wrote:
> Hi,
> 
> --- On Mon, Aug 13, 2012 at 10:51 AM, Christopher Howard
> 
> <christopher.howard at frigidcode.com> wrote:
> | Say, for example, I have the list
> | [[1,2],[3,4]] and want to add 1 to each inner element, resulting in
> | [[2,3],[4,5]].
> 
> \--
> 
> Like this?
> 
> ghci> let xxs = [[1,2], [3,4]]
> 
> ghci> [ [ x+1 | x <- xs] | xs <- xxs ]
> [[2,3],[4,5]]
> 
> SK
> 
> Thanks everyone for the responses. I found the list comprehension
> approach satisfactory, as it allows me to cleanly modify each layer of
> the nested array as I unwrap it:
> 
> code:
> --------
> b = [[ x+1
>     | x <- xs ++ [3] ]
>     | xs <- [[1,2],[3,4]] ]
> 
> *Main> b
> [[2,3,4],[4,5,4]]
> --------
> 
> The only downside is that I have to write the layers out in reverse of
> the way I would normally think of them, but that isn't too big of a
> challenge.
> 
> I'm not sure how that would be done with map in a way that would be neat
> and readable and wouldn't require declaring extra identifiers. I can't
> give a fair evaluation of the Lens approach because I don't understand
> enough of the theory yet.
> 
> --
> frigidcode.com
> indicium.us
> 
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
> 
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
> 
> 
> 
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners



More information about the Beginners mailing list