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: monad nomad gonad gomad (prad)
   2. Re:  Re: monad nomad gonad gomad (Michael Mossey)
   3. Re:  Re: monad nomad gonad gomad (Brandon S Allbery KF8NH)
   4.  Re: monad nomad gonad gomad (prad)
   5.  how to access command line arguments (prad)
   6. Re:  how to access command line arguments (Antoine Latter)
   7. Re:  how to access command line arguments (Marc Weber)
   8. Re:  Re: monad nomad gonad gomad (Michael Mossey)
   9.  leaky folding (Travis Erdman)


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

Message: 1
Date: Sat, 14 Aug 2010 16:51:38 -0700
From: prad <p...@towardsfreedom.com>
Subject: [Haskell-beginners] Re: monad nomad gonad gomad
To: beginners@haskell.org
Message-ID: <20100814165138.5ed34...@gom>
Content-Type: text/plain; charset=US-ASCII

On Fri, 13 Aug 2010 21:39:33 -0700
prad <p...@towardsfreedom.com> wrote:

> "I think It's time for you to get serious with the monads"
> that's just what i'm going to do!
>
i'm asking the question in this thread because i think it has something
to do with monads though i'm not sure. in fact, the problem seems
completely bizarre to me.

i have a function:

mkTxt :: (IConnection conn) => conn -> String -> [String]
mkTxt conn tS = do
    --zzzz <- readFile "zzpubs.htm"
    let wL          = words (rpNls tS)
        ((f,vL):zz) = gtInx wL ["```"]
        rvL         = reverse vL
    doIns wL rvL
        where doIns wL []     = wL
              doIns wL (v:vs) = do
                  let (f,a:b:ss) = splitAt v wL
                  (doIns f vs) ++ ["aoeeuu"] ++ ss

the program compiles and runs fine.
however, if i remove the comment dashes to allow
zzzz <- readFile "zzpubs.htm"

the compiler produces what is to me an incomprehensible rationale for
an error:

====
 gadit.hs:103:4:
    Couldn't match expected type `IO String'
           against inferred type `[String]'
    In a stmt of a 'do' expression: zzzz <- readFile "zzpubs.htm"
    In the expression:
        do { zzzz <- readFile "zzpubs.htm";
             let wL = words (rpNls tS)
                 ((f, vL) : zz) = gtInx wL ...
                 ....;
             doIns wL rvL }
    In the definition of `mkTxt':
        mkTxt conn tS
                = do { zzzz <- readFile "zzpubs.htm";
                       let wL = ...
                           ....;
                       doIns wL rvL }
                where
                    doIns wL [] = wL
                    doIns wL (v : vs)
                            = do { let ...;
                                   .... }
====

i don't do anything with zzzz!!
it merely is the name i'm giving to the monadic computation to read in
a file. in fact, it has nothing to do with the rest of the function
because i don't use it at all.

why is the compiler complaining?


-- 
In friendship,
prad

                                      ... with you on your journey
Towards Freedom
http://www.towardsfreedom.com (website)
Information, Inspiration, Imagination - truly a site for soaring I's




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

Message: 2
Date: Sat, 14 Aug 2010 18:28:03 -0700
From: Michael Mossey <m...@alumni.caltech.edu>
Subject: Re: [Haskell-beginners] Re: monad nomad gonad gomad
To: prad <p...@towardsfreedom.com>
Cc: beginners@haskell.org
Message-ID: <4c6742a3.80...@alumni.caltech.edu>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed


For your string-manipulation problem, I don't think you meant to use 
do-notation. The compiler accepted it because sees it as the list monad, 
and as a coincidence of the way you wrote it, it did what you expected.

Try this, using (let ... in ) syntax.

 > mkTxt :: (IConnection conn) => conn -> String -> [String]
 > mkTxt conn tS =
 >     let wL          = words (rpNls tS)
 >         ((f,vL):zz) = gtInx wL ["```"]
 >         rvL         = reverse vL
 >     in doIns wL rvL
 >         where doIns wL []     = wL
 >               doIns wL (v:vs) =
 >                   let (f,a:b:ss) = splitAt v wL
 >                   in (doIns f vs) ++ ["aoeeuu"] ++ ss

(Untested.)

Next readFile has the signature
readFile :: FilePath -> IO String

So the way I think of it is that any function using it has to return a 
result of "IO <something>"

You would have to call your pure function mkTxt from inside a monadic 
computation:

run :: IO ()
run = do
   zzzz <- readFile "zzpubs.txt"
   ...
   -- assuming mkTxt is modified to accept a third arg
   let result = mkTxt conn ts zzzz
   print result

Finally, yes Haskell complains about type-related faults in identifiers you 
don't use... because it is trying to help you find your mistakes. How does 
it know it wasn't a mistake on your part?

This is an advantage over script languages.

Mike


prad wrote:
> On Fri, 13 Aug 2010 21:39:33 -0700
> prad <p...@towardsfreedom.com> wrote:
> 
>> "I think It's time for you to get serious with the monads"
>> that's just what i'm going to do!
>>
> i'm asking the question in this thread because i think it has something
> to do with monads though i'm not sure. in fact, the problem seems
> completely bizarre to me.
> 
> i have a function:
> 
> mkTxt :: (IConnection conn) => conn -> String -> [String]
> mkTxt conn tS = do
>     --zzzz <- readFile "zzpubs.htm"
>     let wL          = words (rpNls tS)
>         ((f,vL):zz) = gtInx wL ["```"]
>         rvL         = reverse vL
>     doIns wL rvL
>         where doIns wL []     = wL
>               doIns wL (v:vs) = do
>                   let (f,a:b:ss) = splitAt v wL
>                   (doIns f vs) ++ ["aoeeuu"] ++ ss
> 
> the program compiles and runs fine.
> however, if i remove the comment dashes to allow
> zzzz <- readFile "zzpubs.htm"
> 
> the compiler produces what is to me an incomprehensible rationale for
> an error:
> 
> ====
>  gadit.hs:103:4:
>     Couldn't match expected type `IO String'
>            against inferred type `[String]'
>     In a stmt of a 'do' expression: zzzz <- readFile "zzpubs.htm"
>     In the expression:
>         do { zzzz <- readFile "zzpubs.htm";
>              let wL = words (rpNls tS)
>                  ((f, vL) : zz) = gtInx wL ...
>                  ....;
>              doIns wL rvL }
>     In the definition of `mkTxt':
>         mkTxt conn tS
>                 = do { zzzz <- readFile "zzpubs.htm";
>                        let wL = ...
>                            ....;
>                        doIns wL rvL }
>                 where
>                     doIns wL [] = wL
>                     doIns wL (v : vs)
>                             = do { let ...;
>                                    .... }
> ====
> 
> i don't do anything with zzzz!!
> it merely is the name i'm giving to the monadic computation to read in
> a file. in fact, it has nothing to do with the rest of the function
> because i don't use it at all.
> 
> why is the compiler complaining?
> 
> 


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

Message: 3
Date: Sat, 14 Aug 2010 22:07:39 -0400
From: Brandon S Allbery KF8NH <allb...@ece.cmu.edu>
Subject: Re: [Haskell-beginners] Re: monad nomad gonad gomad
To: beginners@haskell.org
Message-ID: <4c674beb.9090...@ece.cmu.edu>
Content-Type: text/plain; charset=UTF-8

-----BEGIN PGP SIGNED MESSAGE-----
Hash: SHA1

On 8/14/10 19:51 , prad wrote:
> mkTxt :: (IConnection conn) => conn -> String -> [String]
(...)
> the compiler produces what is to me an incomprehensible rationale for
> an error:
> 
> ====
>  gadit.hs:103:4:
>     Couldn't match expected type `IO String'
>            against inferred type `[String]'

You didn't specify that mkTxt is in IO; your result type is [String], which
(given your use of the monad machinery) means you return a String in the
List monad.  So, "(zzzz :: String) <- (readFile "zzPubs.htm" :: IO String)",
but because of the List monad in the result type this means that it's
expecting a [String], not an IO String.

- -- 
brandon s. allbery     [linux,solaris,freebsd,perl]      allb...@kf8nh.com
system administrator  [openafs,heimdal,too many hats]  allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university      KF8NH
-----BEGIN PGP SIGNATURE-----
Version: GnuPG v2.0.10 (Darwin)
Comment: Using GnuPG with Mozilla - http://enigmail.mozdev.org/

iEYEARECAAYFAkxnS+sACgkQIn7hlCsL25XmGQCgrhMM6vCzRNMH4deG41od7eD3
l9cAn0a+WbwvkAWC7ikG9mFB6ybIjTKa
=Voo5
-----END PGP SIGNATURE-----


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

Message: 4
Date: Sat, 14 Aug 2010 19:52:34 -0700
From: prad <p...@towardsfreedom.com>
Subject: [Haskell-beginners] Re: monad nomad gonad gomad
To: beginners@haskell.org
Message-ID: <20100814195234.3727e...@gom>
Content-Type: text/plain; charset=US-ASCII

On Sat, 14 Aug 2010 18:28:03 -0700
Michael Mossey <m...@alumni.caltech.edu> wrote:

> Finally, yes Haskell complains about type-related faults in
> identifiers you don't use... because it is trying to help you find
> your mistakes. How does it know it wasn't a mistake on your part?
> 
> This is an advantage over script languages.
>
wow! this is amazing!
i guess when you understand the compiler's intentions, you acquire a
powerful ally!

experimenting in another file, i did something similar:

===========
gtKys conn = do
    z <- readFile "monads.txt"
    r <- quickQuery conn "select key from main" []
    --return $ concat $ map (map fromSql) r
    manip z 

manip f = do
    let wL = words f
    putStrLn $ show wL
==========


this works fine, even though the r quickQuery line is never used.
so i guess one has to try to figure out how to work with the compiler.

part of the feeling i'm getting is that a function should only do one
thing and i likely try to squeeze too much into it.

i'm used to using a lot of print statements to figure out errors, but
may be the idea here is not to make errors because you're functions are
written correctly and are precise.

i'll rethink what i'm writing and how.

-- 
In friendship,
prad

                                      ... with you on your journey
Towards Freedom
http://www.towardsfreedom.com (website)
Information, Inspiration, Imagination - truly a site for soaring I's


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

Message: 5
Date: Sat, 14 Aug 2010 20:39:00 -0700
From: prad <p...@towardsfreedom.com>
Subject: [Haskell-beginners] how to access command line arguments
To: haskellbeginners <beginners@haskell.org>
Message-ID: <20100814203900.2cb6e...@gom>
Content-Type: text/plain; charset=US-ASCII

here's one way:

import System (getArgs)

args <- getArgs

first = head args
last  = last args
and so on.

i can also do this

(first:last:z) <- getArgs

and avoid using head and tail. in fact, this seems nicer because i can
pattern match for a specific series of inputs. however, if the inputs
aren't there (eg say program arg1 only instead of program arg1 arg2),
then the runtime pattern match failure error: 

user error (Pattern match failure in do expression at Tests.hs:14:4-14)

is understandably generated. this of course doesn't happen if i just
use args because there is no pattern matching.

is the former the better way to do it then? or are there other
alternatives?


-- 
In friendship,
prad

                                      ... with you on your journey
Towards Freedom
http://www.towardsfreedom.com (website)
Information, Inspiration, Imagination - truly a site for soaring I's


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

Message: 6
Date: Sat, 14 Aug 2010 22:59:32 -0500
From: Antoine Latter <aslat...@gmail.com>
Subject: Re: [Haskell-beginners] how to access command line arguments
To: prad <p...@towardsfreedom.com>
Cc: haskellbeginners <beginners@haskell.org>
Message-ID:
        <aanlktimrgirnffcos9+fwgsfyfumy_dzv3vdygg4r...@mail.gmail.com>
Content-Type: text/plain; charset=UTF-8

On Sat, Aug 14, 2010 at 10:39 PM, prad <p...@towardsfreedom.com> wrote:
> here's one way:
>
> import System (getArgs)
>
> args <- getArgs
>
> first = head args
> last  = last args
> and so on.
>
> i can also do this
>
> (first:last:z) <- getArgs
>
> and avoid using head and tail. in fact, this seems nicer because i can
> pattern match for a specific series of inputs. however, if the inputs
> aren't there (eg say program arg1 only instead of program arg1 arg2),
> then the runtime pattern match failure error:
>
> user error (Pattern match failure in do expression at Tests.hs:14:4-14)
>
> is understandably generated. this of course doesn't happen if i just
> use args because there is no pattern matching.
>
> is the former the better way to do it then? or are there other
> alternatives?
>

For really simple uses, you can always do something like:

> getMyArgs :: IO (Maybe SomeDataTypeYouWant)
> getMyArgs
>  = do
>  args <- getArgs
>  case args of
>     [pattern, you, want] -> Just $ <parse arguments>
>     _  -> Nothing

Then you can cleanly handle the 'Nothing' case and do whatever is
appropriate for not having arguments.

For more complicated cases, GHC ships with this module for processing
command line arguments:

http://haskell.org/ghc/docs/6.12.1/html/libraries/base-4.2.0.0/System-Console-GetOpt.html

There are also a few packages on hackage:

cmdargs, which is targeted towards programs with multiple operating
modes which have different options:
http://hackage.haskell.org/package/cmdargs

parseargs:
http://hackage.haskell.org/package/parseargs

cmdlib is newer - I haven't seen a release announcement for it, so I
don't know what sets it apart:
http://hackage.haskell.org/package/cmdlib

Antoine


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

Message: 7
Date: Sun, 15 Aug 2010 05:59:39 +0200
From: Marc Weber <marco-owe...@gmx.de>
Subject: Re: [Haskell-beginners] how to access command line arguments
To: beginners <beginners@haskell.org>
Message-ID: <1281844611-sup-...@nixos>
Content-Type: text/plain; charset=UTF-8

Excerpts from prad's message of Sun Aug 15 05:39:00 +0200 2010:
> is the former the better way to do it then? or are there other
> alternatives?
 
If you don't want to use existing option parsers I'd recommend this
style:

args <- getArgs
case args of
  first:last:z -> ...
  _ -> show_usage

where show_usage = print "expected arguments: first last z"

this way you can "die cracefully" if options are passed the program
it didn't expect.

Marc Weber


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

Message: 8
Date: Sun, 15 Aug 2010 00:18:07 -0700
From: Michael Mossey <m...@alumni.caltech.edu>
Subject: Re: [Haskell-beginners] Re: monad nomad gonad gomad
To: beginners <beginners@haskell.org>
Message-ID: <4c6794af.7000...@alumni.caltech.edu>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed



prad wrote:

> part of the feeling i'm getting is that a function should only do one
> thing and i likely try to squeeze too much into it.

I don't think that's universally true, but you may need to stay simple 
while learning.

> 
> i'm used to using a lot of print statements to figure out errors, but
> may be the idea here is not to make errors because you're functions are
> written correctly and are precise.

Look at the Debug.Trace module. You can emit debugging messages in a 
non-safe but usually helpful manner. Be aware that the messages may come in 
an unexpected order due to laziness.

Mike



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

Message: 9
Date: Sun, 15 Aug 2010 00:58:49 -0700 (PDT)
From: Travis Erdman <traviserd...@yahoo.com>
Subject: [Haskell-beginners] leaky folding
To: beginners@haskell.org
Message-ID: <934203.63868...@web114701.mail.gq1.yahoo.com>
Content-Type: text/plain; charset=us-ascii

in the code below, finalmap seems fast enough ... but it has a space leak.  
otoh, finalmap'rnf runs in constant space, but its performance is terrible, at 
least 4x slower than finalmap.

this is a common problem i'm having ... foldl' isn't strict enough, but 
foldl'rnf kills performance.  and not only with IntMap as the cumulating data 
structure, but others as well.

any ideas on this one?  how can i get a fast fold in constant space?  

thanks again,

travis


{-# LANGUAGE BangPatterns #-}

import System.Environment
import Foreign (unsafePerformIO)
import System.Random.Mersenne
import Data.List
import Control.DeepSeq
import Control.Parallel.Strategies
import qualified Data.IntMap as IntMap

mersennegen = unsafePerformIO $ newMTGen Nothing
infrandoms =  unfoldr ( Just . splitAt 3) $ map (\x -> abs (x `mod` n)) 
(unsafePerformIO $ (randoms mersennegen)::[Int])

n = 200

foldl'rnf :: NFData a => (a -> b -> a) -> a -> [b] -> a
foldl'rnf f z xs = lgo z xs
    where
        lgo z []     = z
        lgo !z (x:xs) = lgo (runEval (rdeepseq (f z x))) xs    

startmap = IntMap.fromDistinctAscList $ zip [0..] [1..n]        

finalmap x = foldl' g startmap (take x infrandoms)
finalmap'rnf x = foldl'rnf g startmap (take x infrandoms)

g:: IntMap.IntMap Int -> [Int] -> IntMap.IntMap Int
g !a [x,y,z] = IntMap.adjust (const $ y + (a IntMap.! z) `mod` n) x a 

main = do  
        args <- getArgs  
        print $ finalmap (read $ head args)


      


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

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


End of Beginners Digest, Vol 26, Issue 31
*****************************************

Reply via email to