
Hi All, At the moment I have a list of lists. The inner list is a coordinate, like (x,y) but is [x,y] instead. What I would like to do is group all the x's into one list, and the y's into another. I know I can do this with calling 2 maps on the container, but I would also like to do this in one iteration. Does anyone have any ideas? Thanks in advance, Bryce

Hi,
On 28 January 2013 18:37, Bryce Verdier
I know I can do this with calling 2 maps on the container, but I would also like to do this in one iteration.
As a learning experience, may I suggest you post the code you would have written with two maps? Then we can try and improve on that to have only one map. Best, -- Ozgur Akgun

So I have a text full of x and y coordinates in the for x_y new line delimited. Here is the first 3 lines: 68_1 153_16099247764943158 153_775041589 I'm massaging the data to run a liner regression on it. At the moment the program I'm writing looks like this (still a work in progress...): module Main where import qualified Data.Text as T import qualified Data.Text.IO as TI import Numeric.GSL.Fitting.Linear import Data.Packed.Vector buildList :: IO [[T.Text]] buildList = TI.readFile "lin_reg_data.txt" >>= return . map (T.split (=='_')) . T.lines --main :: IO () --main = do -- values <- buildList -- let heads = fromList $ map (\x -> read (T.unpack . head $ x):: Double) values -- let lasts = fromList $ map (\x -> read (T.unpack . last $ x):: Double) values -- print linear heads lasts I'm just trying to find a way to not iterate over "vaues" twice as that seems like a waste of computing time to me. Of course any advice on this would be appreciated. Bryce On 01/28/2013 10:42 AM, Ozgur Akgun wrote:
Hi,
On 28 January 2013 18:37, Bryce Verdier
mailto:bryceverdier@gmail.com> wrote: I know I can do this with calling 2 maps on the container, but I would also like to do this in one iteration.
As a learning experience, may I suggest you post the code you would have written with two maps? Then we can try and improve on that to have only one map.
Best,
-- Ozgur Akgun
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners

Hi,
You can use foldl (\(fx, fy) [x,y] -> (x:fx, y:fy)) ([],[])
Thanks
Divyanshu Ranjan
On Tue, Jan 29, 2013 at 12:07 AM, Bryce Verdier
Hi All,
At the moment I have a list of lists. The inner list is a coordinate, like (x,y) but is [x,y] instead. What I would like to do is group all the x's into one list, and the y's into another. I know I can do this with calling 2 maps on the container, but I would also like to do this in one iteration.
Does anyone have any ideas?
Thanks in advance, Bryce
______________________________**_________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/**mailman/listinfo/beginnershttp://www.haskell.org/mailman/listinfo/beginners

On Mon, Jan 28, 2013 at 10:37:53AM -0800, Bryce Verdier wrote:
Hi All,
At the moment I have a list of lists. The inner list is a coordinate, like (x,y) but is [x,y] instead. What I would like to do is group all the x's into one list, and the y's into another. I know I can do this with calling 2 maps on the container, but I would also like to do this in one iteration.
This can be done using the 'transpose' function from Data.List. -Brent

On 01/28/2013 11:24 AM, Brent Yorgey wrote:
On Mon, Jan 28, 2013 at 10:37:53AM -0800, Bryce Verdier wrote:
Hi All,
At the moment I have a list of lists. The inner list is a coordinate, like (x,y) but is [x,y] instead. What I would like to do is group all the x's into one list, and the y's into another. I know I can do this with calling 2 maps on the container, but I would also like to do this in one iteration. This can be done using the 'transpose' function from Data.List.
-Brent
_______________________________________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/mailman/listinfo/beginners
That was exactly what I was looking for. Thank you Brent! Bryce

On Monday, 28. January 2013 19:37:53 Bryce Verdier wrote:
Hi All,
At the moment I have a list of lists. The inner list is a coordinate, like (x,y) but is [x,y] instead. What I would like to do is group all the x's into one list, and the y's into another. I know I can do this with calling 2 maps on the container, but I would also like to do this in one iteration.
Something like this? groupMe = foldl (\[rx,ry] [x,y] -> [x:rx,y:ry]) [[],[]] *Main> groupMe [[1,2],[1,3],[2,3]] [[2,1,1],[3,3,2]] -- Martin

On 01/28/2013 11:32 AM, Martin Drautzburg wrote:
On Monday, 28. January 2013 19:37:53 Bryce Verdier wrote:
Hi All,
At the moment I have a list of lists. The inner list is a coordinate, like (x,y) but is [x,y] instead. What I would like to do is group all the x's into one list, and the y's into another. I know I can do this with calling 2 maps on the container, but I would also like to do this in one iteration. Something like this? groupMe = foldl (\[rx,ry] [x,y] -> [x:rx,y:ry]) [[],[]]
*Main> groupMe [[1,2],[1,3],[2,3]] [[2,1,1],[3,3,2]] Thank you all for your responses. This is what I ultimately went with (pasted below). If anyone would like to share a way to improve this (because I know it can be), please share. I'm still learning. :)
module Main where import qualified Data.Text as T import qualified Data.Text.IO as TI (readFile) import Data.List (transpose) import Numeric.GSL.Fitting.Linear (linear) import Data.Packed.Vector (fromList) buildList :: IO [[T.Text]] buildList = TI.readFile "lin_reg_data.txt" >>= return . transpose . map (T.split (=='_')) . T.lines main :: IO () main = do values <- buildList let values2 = map (fromList . map (\x -> read (T.unpack x):: Double)) values print [linear (head values2) (last values2)] Warm regards, Bryce

Hi,
What is the point of using Text here?
You may rewrite buildList as follows (using <$> from Control.Applicative):
buildList = transpose . map (T.split (=='_')) . T.lines <$> TI.readFile
"lin_reg_data.txt"
Regards
Sylvain
2013/1/28 Bryce Verdier
On 01/28/2013 11:32 AM, Martin Drautzburg wrote:
On Monday, 28. January 2013 19:37:53 Bryce Verdier wrote:
Hi All,
At the moment I have a list of lists. The inner list is a coordinate, like (x,y) but is [x,y] instead. What I would like to do is group all the x's into one list, and the y's into another. I know I can do this with calling 2 maps on the container, but I would also like to do this in one iteration.
Something like this? groupMe = foldl (\[rx,ry] [x,y] -> [x:rx,y:ry]) [[],[]]
*Main> groupMe [[1,2],[1,3],[2,3]] [[2,1,1],[3,3,2]]
Thank you all for your responses. This is what I ultimately went with (pasted below). If anyone would like to share a way to improve this (because I know it can be), please share. I'm still learning. :)
module Main where
import qualified Data.Text as T import qualified Data.Text.IO as TI (readFile) import Data.List (transpose) import Numeric.GSL.Fitting.Linear (linear) import Data.Packed.Vector (fromList)
buildList :: IO [[T.Text]] buildList = TI.readFile "lin_reg_data.txt" >>= return . transpose . map (T.split (=='_')) . T.lines
main :: IO () main = do values <- buildList let values2 = map (fromList . map (\x -> read (T.unpack x):: Double)) values print [linear (head values2) (last values2)]
Warm regards, Bryce
______________________________**_________________ Beginners mailing list Beginners@haskell.org http://www.haskell.org/**mailman/listinfo/beginnershttp://www.haskell.org/mailman/listinfo/beginners
participants (6)
-
Brent Yorgey
-
Bryce Verdier
-
divyanshu ranjan
-
Martin Drautzburg
-
Ozgur Akgun
-
Sylvain HENRY