cleanest way to unwrap a list?

Hi. Is the some generic, clean syntax to unwrap a nested list, modify the value, and put it back together? 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]]. After reading about the list monad, I was rather excited, because I (mistakenly) thought something like this would work: code: -------- a = do b <- [[1,2],[3,4]] c <- b return (c + 1) -------- That would be awesome, because I would be able to modify the list at each level of unwrapping, while leaving the code very neat and readable. However, what the above example actually does is produce a /single/ list from the values: code: -------- *Main> a [2,3,4,5] -------- Obviously wishing won't change how the list monad works, but I thought it might be worth asking if there is some other monad or syntactic trick that does something along the lines of what I am looking for. -- frigidcode.com indicium.us

Hi,
--- On Mon, Aug 13, 2012 at 10:51 AM, Christopher Howard

On Mon, 13 Aug 2012 07:37:48 +0200, Shakthi Kannan
Hi,
--- On Mon, Aug 13, 2012 at 10:51 AM, Christopher Howard
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]]
Or this?
map (map (+ 1)) [[1,2], [3,4]] [[2,3],[4,5]]
Regards, Henk-Jan van Tuyl -- http://Van.Tuyl.eu/ http://members.chello.nl/hjgtuyl/tourdemonad.html Haskell programming --

On 08/12/2012 09:37 PM, Shakthi Kannan wrote:
Hi,
--- On Mon, Aug 13, 2012 at 10:51 AM, Christopher Howard
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

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@uvm.edu
On Aug 13, 2012, at 6:41 PM, Christopher Howard
On 08/12/2012 09:37 PM, Shakthi Kannan wrote:
Hi,
--- On Mon, Aug 13, 2012 at 10:51 AM, Christopher Howard
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@haskell.org http://www.haskell.org/mailman/listinfo/beginners

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@uvm.edu
On Aug 13, 2012, at 6:41 PM, Christopher Howard
wrote: On 08/12/2012 09:37 PM, Shakthi Kannan wrote:
Hi,
--- On Mon, Aug 13, 2012 at 10:51 AM, Christopher Howard
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@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

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@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@uvm.edu
On Aug 13, 2012, at 6:41 PM, Christopher Howard
> wrote: On 08/12/2012 09:37 PM, Shakthi Kannan wrote:
Hi,
--- On Mon, Aug 13, 2012 at 10:51 AM, Christopher Howard
> 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@haskell.org http://www.haskell.org/**mailman/listinfo/beginnershttp://www.haskell.org/mailman/listinfo/beginners
______________________________**_________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/**mailman/listinfo/beginnershttp://www.haskell.org/mailman/listinfo/beginners
______________________________**_________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/**mailman/listinfo/beginnershttp://www.haskell.org/mailman/listinfo/beginners

This is a bit more "functional". The coordinates are the opposite way
around, and it can probably be expressed a bit more concisely, but
I'll leave that to you. This is the basic idea.
-- maps over a list supplying also the 'index'
mapi f = map (uncurry f) . zip [0..]
-- maps over a list supplying also the coordinate pair
mapii f a = mapi f' a
where f' i x = mapi (curry f $ i) x
m0 = [[1,2,3], [4,5,6], [7,8,9]]
f (1,1) a = a+1
f (0,2) a = a-1
f (_,_) a = a
mapii f m0 -- [[1,2,3],[4,6,6],[6,8,9]]
Peter
On 14 August 2012 22:50, Carlos J. G. Duarte
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
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@uvm.edu
On Aug 13, 2012, at 6:41 PM, Christopher Howard
wrote: On 08/12/2012 09:37 PM, Shakthi Kannan wrote:
Hi,
--- On Mon, Aug 13, 2012 at 10:51 AM, Christopher Howard
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@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

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
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@uvm.edu
On Aug 13, 2012, at 6:41 PM, Christopher Howard
wrote: On 08/12/2012 09:37 PM, Shakthi Kannan wrote: Hi,
--- On Mon, Aug 13, 2012 at 10:51 AM, Christopher Howard
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@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Maybe this is overkill, but if you want a more generic way for accessing and changing nested immutable data in general, you could check this package out as it is pretty exciting (to me at least): http://hackage.haskell.org/package/lens For more information on exactly what a lens is, read here: http://dl.dropbox.com/u/7810909/media/doc/lenses.pdf Cheers, Ben On Monday, 13 August 2012 at 3:21 PM, Christopher Howard wrote:
Hi. Is the some generic, clean syntax to unwrap a nested list, modify the value, and put it back together? 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]].
After reading about the list monad, I was rather excited, because I (mistakenly) thought something like this would work:
code: -------- a = do b <- [[1,2],[3,4]] c <- b return (c + 1) --------
That would be awesome, because I would be able to modify the list at each level of unwrapping, while leaving the code very neat and readable. However, what the above example actually does is produce a /single/ list from the values:
code: -------- *Main> a [2,3,4,5] --------
Obviously wishing won't change how the list monad works, but I thought it might be worth asking if there is some other monad or syntactic trick that does something along the lines of what I am looking for.
-- frigidcode.com (http://frigidcode.com) indicium.us (http://indicium.us)
_______________________________________________ Beginners mailing list Beginners@haskell.org (mailto:Beginners@haskell.org) http://www.haskell.org/mailman/listinfo/beginners

On Sun, 12 Aug 2012, Christopher Howard
Hi. Is the some generic, clean syntax to unwrap a nested list, modify the value, and put it back together? 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]].
I think there is a forgetful functor from a part of Haskell to Scheme, and this code lies in the image of this functor:
(define map-1+ (lambda (l) (map (lambda (n) (+ 1 n)) l))) #<unspecified> (map-1+ (list 0 1 2 3 4)) (1 2 3 4 5) (define map-map-1+ (lambda (l-of-l-of-numbers) (map map-1+ l-of-l-of-numbers))) #<unspecified> (map-map-1+ (list (list 1 2) (list 3 4))) ((2 3) (4 5)) (quit)
Process scheme finished Further we have for this forgetful functor, that the original Haskell code and the transformed-to-Scheme code have the "same" running behavior, and the "same" input output behavior. And under this functor the image of the object called "map" in Haskell is the object called "map" in Scheme. Haskell has map in the prelude: map :: (a -> b) -> [a] -> [b] map f xs is the list obtained by applying f to each element of xs, i.e., map f [x1, x2, ..., xn] == [f x1, f x2, ..., f xn] map f [x1, x2, ...] == [f x1, f x2, ...] Above quote taken from http://www.haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html So, likely, I do not know Haskell, something like: m1 = map 1+ l m2 = map m1 l should work. Likely a bit more source code might be required for various Haskell systems. And the procedure 1+ might have to be defined, up to getting the right type of number specified, as 1+ n = (n + 1) oo--JS.
After reading about the list monad, I was rather excited, because I (mistakenly) thought something like this would work:
code: -------- a = do b <- [[1,2],[3,4]] c <- b return (c + 1) --------
That would be awesome, because I would be able to modify the list at each level of unwrapping, while leaving the code very neat and readable. However, what the above example actually does is produce a /single/ list from the values:
code: -------- *Main> a [2,3,4,5] --------
Obviously wishing won't change how the list monad works, but I thought it might be worth asking if there is some other monad or syntactic trick that does something along the lines of what I am looking for.
-- frigidcode.com indicium.us

On Mon, 13 Aug 2012, Jay Sulzberger wrote:
On Sun, 12 Aug 2012, Christopher Howard
wrote: Hi. Is the some generic, clean syntax to unwrap a nested list, modify the value, and put it back together? 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]].
I think there is a forgetful functor from a part of Haskell to Scheme, and this code lies in the image of this functor:
(define map-1+ (lambda (l) (map (lambda (n) (+ 1 n)) l))) #<unspecified> (map-1+ (list 0 1 2 3 4)) (1 2 3 4 5) (define map-map-1+ (lambda (l-of-l-of-numbers) (map map-1+ l-of-l-of-numbers))) #<unspecified> (map-map-1+ (list (list 1 2) (list 3 4))) ((2 3) (4 5)) (quit)
Process scheme finished
Further we have for this forgetful functor, that the original Haskell code and the transformed-to-Scheme code have the "same" running behavior, and the "same" input output behavior. And under this functor the image of the object called "map" in Haskell is the object called "map" in Scheme.
Haskell has map in the prelude:
map :: (a -> b) -> [a] -> [b]
map f xs is the list obtained by applying f to each element of xs, i.e.,
map f [x1, x2, ..., xn] == [f x1, f x2, ..., f xn] map f [x1, x2, ...] == [f x1, f x2, ...]
Above quote taken from
http://www.haskell.org/ghc/docs/latest/html/libraries/base/Prelude.html
So, likely, I do not know Haskell, something like:
m1 = map 1+ l m2 = map m1 l
Ah, above likely wrong. OK, what about m1 l = map 1+ l m2 l = map m1 l or perhaps m1 = map 1+ m2 = map m1 oo--JS.
should work. Likely a bit more source code might be required for various Haskell systems. And the procedure 1+ might have to be defined, up to getting the right type of number specified, as
1+ n = (n + 1)
oo--JS.
After reading about the list monad, I was rather excited, because I (mistakenly) thought something like this would work:
code: -------- a = do b <- [[1,2],[3,4]] c <- b return (c + 1) --------
That would be awesome, because I would be able to modify the list at each level of unwrapping, while leaving the code very neat and readable. However, what the above example actually does is produce a /single/ list from the values:
code: -------- *Main> a [2,3,4,5] --------
Obviously wishing won't change how the list monad works, but I thought it might be worth asking if there is some other monad or syntactic trick that does something along the lines of what I am looking for.
-- frigidcode.com indicium.us

What about just map (map f) xxs where for your example xxs == [[1,2], [3,4]] f == (+1) Graham On 13/08/2012 1:21 AM, Christopher Howard wrote:
Hi. Is the some generic, clean syntax to unwrap a nested list, modify the value, and put it back together? 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]].
After reading about the list monad, I was rather excited, because I (mistakenly) thought something like this would work:
code: -------- a = do b <- [[1,2],[3,4]] c <- b return (c + 1) --------
That would be awesome, because I would be able to modify the list at each level of unwrapping, while leaving the code very neat and readable. However, what the above example actually does is produce a /single/ list from the values:
code: -------- *Main> a [2,3,4,5] --------
Obviously wishing won't change how the list monad works, but I thought it might be worth asking if there is some other monad or syntactic trick that does something along the lines of what I am looking for.
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Another vote for
map (map (+1)) [[1,2],[2,3]]
though I rather prefer
(map . map) (+1) [[1,2],[2,3]]
or even
(map . map) (+1) $ [[1,2],[2,3]]
====
Jack Henahan
jhenahan@uvm.edu
On Aug 13, 2012, at 1:21 AM, Christopher Howard
Hi. Is the some generic, clean syntax to unwrap a nested list, modify the value, and put it back together? 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]].
After reading about the list monad, I was rather excited, because I (mistakenly) thought something like this would work:
code: -------- a = do b <- [[1,2],[3,4]] c <- b return (c + 1) --------
That would be awesome, because I would be able to modify the list at each level of unwrapping, while leaving the code very neat and readable. However, what the above example actually does is produce a /single/ list from the values:
code: -------- *Main> a [2,3,4,5] --------
Obviously wishing won't change how the list monad works, but I thought it might be worth asking if there is some other monad or syntactic trick that does something along the lines of what I am looking for.
-- frigidcode.com indicium.us
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
participants (11)
-
Ben Kolera
-
Carlos J. G. Duarte
-
Christopher Howard
-
Graham Gill
-
Henk-Jan van Tuyl
-
Jack Henahan
-
Jay Sulzberger
-
Nick Vanderweit
-
Peter Hall
-
Shakthi Kannan
-
Tim Perry