Send Beginners mailing list submissions to
        beginners@haskell.org

To subscribe or unsubscribe via the World Wide Web, visit
        http://www.haskell.org/mailman/listinfo/beginners
or, via email, send a message with subject or body 'help' to
        beginners-requ...@haskell.org

You can reach the person managing the list at
        beginners-ow...@haskell.org

When replying, please edit your Subject line so it is more specific
than "Re: Contents of Beginners digest..."


Today's Topics:

   1. Re:  Help with CSV (Hong Yang)
   2. Re:  Help with CSV (Erik de Castro Lopo)
   3.  Re: number formatting with locale (Heinrich Apfelmus)
   4. Re:  Re: number formatting with locale (Dmitry Simonchik)
   5. Re:  Urgent: Defining Momory data Types in Haskell (Brent Yorgey)
   6. Re:  Re: number formatting with locale (Wirt Wolff)
   7.  Problems defining a type with a multiplication   function
      (Amy de Buitl?ir)
   8. Re:  Problems defining a type with a      multiplication function
      (John Dorsey)


----------------------------------------------------------------------

Message: 1
Date: Mon, 7 Sep 2009 21:35:29 -0500
From: Hong Yang <hyang...@gmail.com>
Subject: Re: [Haskell-beginners] Help with CSV
To: Keith Sheppard <keiths...@gmail.com>
Cc: beginners@haskell.org
Message-ID:
        <f31db34d0909071935m5b86f670xb8beb64d5cc10...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Thanks for your reply. I have a working program now using Text.CSV module.

Do you see any that can be improved?

When I print, the screen reads "Just "abc"". How can I get rid of "Just" in
the most elegant way?

Thanks,

Hong

-- file: ch22/PodMain.hs
module Main where

import System.Environment (getArgs)
import Text.CSV
import qualified Data.Map as M

main = do
       [args] <- getArgs
       result <- parseCSVFromFile args
       case result of
            Left errmsg    -> putStrLn "Error when parsing!"
            Right contents -> map_header_records contents

map_header_records :: CSV -> IO ()
map_header_records [] = return ()
map_header_records (x:xs) = process x xs

process :: [String] -> CSV -> IO ()
process x [] = return ()
process x (y:ys) = do
    let tuple = zip x y
    let hash = M.fromList tuple
    putStrLn (show (M.lookup "name" hash))
    process x ys


On Wed, Sep 2, 2009 at 8:23 PM, Keith Sheppard <keiths...@gmail.com> wrote:

> Not quite code but...
>
> here is an example of parsing CSV
> http://book.realworldhaskell.org/read/using-parsec.html and here is a
> library that you can use which is similar
> http://hackage.haskell.org/package/csv
>
> These approaches give you a 2D String list that you can do whatever
> you want with.
>
> if you need to turn a string into a double and you know the string is
> well formed i think the syntax looks like
>
> > let doubleVal = read stringVal :: Double
>
> There are better ways to do this if you need to be able to handle
> formatting errors but I don't know them off the top of my head
>
> -Keith
>
> On Wed, Sep 2, 2009 at 6:40 PM, Hong Yang<hyang...@gmail.com> wrote:
> > I need to process csv files that have the characteristics as follows:
> > 1)    each file has thousands of columns which have String, Int, and
> Double
> > types
> > 2)    the number of columns may change
> > 3)    for those columns whose name do not change, their location may
> change
> >
> > I want to process some columns in 3) using Haskell.
> >
> > In Perl, I can easily have the code like below:
> >
> > use Text::CSV;
> > my $csv = Text::CSV->new( { allow_whitespace => 1 } );
> > open my $temp, "<", "temp.csv" or die "Cannot open temp.csv! ($!)";
> > my @fields = @{ $csv->getline($temp) };
> > $csv->column_names(@fields);
> > while ( my $hr = $csv->getline_hr($temp) ) {
> >     my $sn = $hr->{"UNIT:unitSerialNumber"};
> >     # processing goes here ...
> > }
> > close $temp;
> >
> > Can someone please give me an equivalent code in Haskell? Then I can
> digest
> > and expand it.
> >
> > Thanks,
> >
> > Hong
> >
> > _______________________________________________
> > Beginners mailing list
> > Beginners@haskell.org
> > http://www.haskell.org/mailman/listinfo/beginners
> >
> >
>
>
>
> --
> keithsheppard.name
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20090907/971883c0/attachment-0001.html

------------------------------

Message: 2
Date: Tue, 8 Sep 2009 12:45:30 +1000
From: Erik de Castro Lopo <mle...@mega-nerd.com>
Subject: Re: [Haskell-beginners] Help with CSV
To: beginners@haskell.org
Message-ID: <20090908124530.6e280a53.mle...@mega-nerd.com>
Content-Type: text/plain; charset=US-ASCII

Hong Yang wrote:

> Thanks for your reply. I have a working program now using Text.CSV module.
> 
> Do you see any that can be improved?
> 
> When I print, the screen reads "Just "abc"". How can I get rid of "Just" in
> the most elegant way?

Try Data.Maybe.fromMaybe:

http://haskell.org/ghc/docs/latest/html/libraries/base/Data-Maybe.html#v:fromMaybe

Erik
-- 
----------------------------------------------------------------------
Erik de Castro Lopo
http://www.mega-nerd.com/


------------------------------

Message: 3
Date: Tue, 08 Sep 2009 10:42:19 +0200
From: Heinrich Apfelmus <apfel...@quantentunnel.de>
Subject: [Haskell-beginners] Re: number formatting with locale
To: beginners@haskell.org
Message-ID: <h855db$l3...@ger.gmane.org>
Content-Type: text/plain; charset=UTF-8

Dmitry Simonchik wrote:
> I'm trying to print out Double in russian locale (we use "," as decimal
> separator insetad of "."). I'm trying to set locale with
> System.Locale.SetLocale like
> 
> setLocale LC_ALL $ Just "ru_RU.UTF-8"
> 
> this returns Just "ru_RU.UTF-8", so it seems that function call succeeded,
> but when I call
> 
> show 20.2
> 
> it just prints 20.2 and not desired 20,2
> 
> Can anyone please help?

By design,  show  and  read  don't use the locale. Not to mention that
since Haskell is pure, it is *impossible* for the expression  show 20.2
:: String  to depend on the current locale.

I have never tried to use locales in Haskell, maybe someone else can
help. Most likely, you'll need to do foreign imports of C functions.


Regards,
apfelmus

--
http://apfelmus.nfshost.com



------------------------------

Message: 4
Date: Tue, 8 Sep 2009 12:47:43 +0400
From: Dmitry Simonchik <d...@simonchik.net>
Subject: Re: [Haskell-beginners] Re: number formatting with locale
To: Heinrich Apfelmus <apfel...@quantentunnel.de>
Cc: beginners@haskell.org
Message-ID:
        <80eb7b2e0909080147j615d556fw73cc4022a29b4...@mail.gmail.com>
Content-Type: text/plain; charset="utf-8"

Not to mention that
> since Haskell is pure, it is *impossible* for the expression  show 20.2
> :: String  to depend on the current locale.
>

This is a very valuable remark. Thanks! I will think about using some
special functions to read and write numbers depending on current locale.
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20090908/469ee3e1/attachment-0001.html

------------------------------

Message: 5
Date: Tue, 8 Sep 2009 07:52:09 -0400
From: Brent Yorgey <byor...@seas.upenn.edu>
Subject: Re: [Haskell-beginners] Urgent: Defining Momory data Types in
        Haskell
To: beginners@haskell.org
Message-ID: <20090908115209.ga29...@seas.upenn.edu>
Content-Type: text/plain; charset=us-ascii

On Mon, Sep 07, 2009 at 06:37:16AM +0000, Akshay Dave wrote:
> 
> (Memory maps I to Z)
> lookup m i = <current value of i>  ( meaning lookup for I in memory m)

You shouldn't need to use anything so crass as pointers to accomplish
this.  Try taking a look at the Map data structure in Data.Map:

  
http://hackage.haskell.org/packages/archive/containers/0.2.0.1/doc/html/Data-Map.html

If there is some reason Data.Map won't work for you, please explain
why so we can better understand what you are trying to do.

-Brent



------------------------------

Message: 6
Date: Tue, 08 Sep 2009 08:31:10 -0600
From: Wirt Wolff <wirtwo...@gmail.com>
Subject: Re: [Haskell-beginners] Re: number formatting with locale
To: Dmitry Simonchik <d...@simonchik.net>
Cc: beginners <beginners@haskell.org>
Message-ID: <1252420124-sup-1...@chigamba>
Content-Type: text/plain; charset=UTF-8

Excerpts from Dmitry Simonchik's message of Tue Sep 08 02:47:43 -0600 2009:
> Not to mention that
> > since Haskell is pure, it is *impossible* for the expression  show 20.2
> > :: String  to depend on the current locale.
> >
> 
> This is a very valuable remark. Thanks! I will think about using some
> special functions to read and write numbers depending on current locale.

The i18n module from hackage is worth a look for this:

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/i18n

-- 
wmw


------------------------------

Message: 7
Date: Wed, 9 Sep 2009 21:51:34 +0100
From: Amy de Buitl?ir <a...@nualeargais.ie>
Subject: [Haskell-beginners] Problems defining a type with a
        multiplication  function
To: beginners@haskell.org
Message-ID:
        <77b28c350909091351o2c5c288bi6851b3cde1dd4...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

I'm trying to define a Quaternion, which is sort of a four-element vector
with special rules for multiplication.

----- Quaternion.hs -----
data Quaternion = Quaternion Double Double Double Double
                  deriving (Show)

(*) :: (Quaternion a) => a -> a -> a
(*) (Quaternion w1 x1 y1 z1) (Quaternion w2 x2 y2 z2) = Quaternion w x y z
        where w = w1*w2 - x1*x2 - y1*y2 - z1*z2
              x = x1*w2 + w1*x2 + y1*z2 - z1*y2
              y = w1*y2 - x1*z2 + y1*w2 + z1*x2
              z = w1*z2 + x1*y2 - y1*x2 + z1*w2

----- end code -----

When I try to load this into ghci, I get:

Quaternion.hs:6:13:
    Ambiguous occurrence `*'
    It could refer to either `Main.*', defined at Quaternion.hs:5:0
                          or `Prelude.*', imported from Prelude

... and lots more messages like that. I understand roughly what the message
means, but I don't know how to tell it that when I use "*" within the
definition, I just want ordinary multiplication. Thanks in advance for any
help!

Amy
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20090909/f2a3ffee/attachment-0001.html

------------------------------

Message: 8
Date: Wed, 9 Sep 2009 17:02:47 -0400
From: John Dorsey <hask...@colquitt.org>
Subject: Re: [Haskell-beginners] Problems defining a type with a
        multiplication function
To: beginners@haskell.org
Message-ID: <20090909210247.gi14...@colquitt.org>
Content-Type: text/plain; charset=us-ascii

Amy,

> Quaternion.hs:6:13:
>     Ambiguous occurrence `*'
>     It could refer to either `Main.*', defined at Quaternion.hs:5:0
>                           or `Prelude.*', imported from Prelude
> 
> ... and lots more messages like that. I understand roughly what the message
> means, but I don't know how to tell it that when I use "*" within the
> definition, I just want ordinary multiplication. Thanks in advance for any

You're redefining (*) in Main, which creates the ambiguity, which is the
problem.  One alternative is, instead of creating a new ambiguous (*), is
use the existing one, and make it apply to your type.

The existing (*) belongs to the typeclass Num.  You can make your type an
instance of Num, with your definition of (*):

instance Num (Quaternion a) where
  q1 * q2 = ...
  q1 + q2 = undefined -- or, better, a valid definition
  q1 - q2 = undefined
  ...

You'll find that this cascades into requiring you to define a handful of
other class functions (+, -, negate, abs, signum, fromInteger) and you'll
need Eq and Show instances.  You can derive the latter, and you can give
trivial (undefined or error) definitions for, say, negate if you won't be
using it.

Hope this helps.

John



------------------------------

_______________________________________________
Beginners mailing list
Beginners@haskell.org
http://www.haskell.org/mailman/listinfo/beginners


End of Beginners Digest, Vol 15, Issue 6
****************************************

Reply via email to