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:  Re: multreplace (jean verdier)
   2.  Re: the role of assignments (prad)
   3. Re:  Re: multreplace (Daniel Fischer)
   4. Re:  Re: multreplace (Daniel Fischer)
   5.  Re: Enforcing Monad Laws (Heinrich Apfelmus)
   6. Re:  Re: the role of assignments (edgar klerks)
   7. Re:  Re: the role of assignments (Benjamin Edwards)
   8. Re:  Re: multreplace (Patrick LeBoutillier)


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

Message: 1
Date: Fri, 02 Jul 2010 09:21:00 +0200
From: jean verdier <verdier.j...@gmail.com>
Subject: Re: [Haskell-beginners] Re: multreplace
To: prad <p...@towardsfreedom.com>
Cc: beginners@haskell.org
Message-ID: <1278055260.2275.2.ca...@localhost>
Content-Type: text/plain; charset="UTF-8"

I think your first attempt using list comprehension is nearly ok but is
in fact a fold:

multRepl str ss rs = foldl (uncurry . replace) str (zip ss rs)

or something similar.

On Thu, 2010-07-01 at 23:58 -0700, prad wrote:
> On Thu, 1 Jul 2010 22:31:28 -0700
> prad <p...@towardsfreedom.com> wrote:
> 
> > so back to
> > the drawing board!
> >
> here's what emerged:
> 
> ======
> #!/usr/bin/env runghc
> 
> module Main where
> 
> import Useful as U
> 
> main = do
> 
>     let str = "This is original string"
>     let ss  = ["orig","ing"]
>     let rs  = ["very orig","ucture"]
> 
>     putStrLn $ head (multRepl str ss rs)
>     
>     
> --multRepl :: String -> [String] -> [String] -> [String]
> multRepl [] _ _             = []
> multRepl str (s:ss) (r:rs)  = do
>     let newStr = U.replace str s r
>     if (length ss) == 0 
>        then return newStr 
>        else multRepl newStr ss rs 
> =======
> 
> this does produce the correct output:
> This is very original structure
> 
> 
> and here are my questions:
> 
> 1. the type
> *Main Useful> :t multRepl 
> multRepl :: (Eq t) => [t] -> [[t]] -> [[t]] -> [[t]]
> 
> but i have it returning newStr which equals U.replace str s r
> and the type of U.replace is String as shown below
> *Main Useful> :t Useful.replace
> Useful.replace :: (Eq a) => [a] -> [a] -> [a] -> [a]
> 
> so why is it returning [String] when newStr isn't a list of strings?
> 
> 2. is the way i've done it proper haskellian? it took me quite some
> time to think this out trying to find my way through the fog of
> imperative programming.
> 
> (my apologies for replying to my own posts - as well as my
> appreciation for your assistance)
> 




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

Message: 2
Date: Fri, 2 Jul 2010 00:26:09 -0700
From: prad <p...@towardsfreedom.com>
Subject: [Haskell-beginners] Re: the role of assignments
To: beginners@haskell.org
Message-ID: <20100702002609.5bab2...@gom>
Content-Type: text/plain; charset=US-ASCII

On Fri, 2 Jul 2010 03:27:00 +0200
Ertugrul Soeylemez <e...@ertes.de> wrote:

> I think, you're building up the wrong intuition here.  Let me try to
> correct it.
thank you, ertugrul!
your detailed, example-laden explanation was wonderful!


> This is not an assignment.  You just give the result of the
> computation a name.
>
this is very meaningful to me.
thinking about it as you say really makes a difference in clarity for
me.


> getLine is a computation of type IO String, so 'line' is of type
> String. There is no conversion involved, because actually there is no
> "running" involved at all.
>
ya this too is something to understand - my reasoning has been
pythonish and that is likely a big part of the problem.


> As you can see from its type, it's
> also an IO computation:
> 
>   main :: IO ()
> 
this came as big surprise - but of course, now i think "what else could
it possibly be?"


> Whenever an equals sign is involved, this is
> just name giving, not an 'assignment' in the usual sense.
>
again this requires a conceptual shift for me.


> You can view GHCi's
> command line as one 'do' block, which gets executed as you type it.
> That's why you need 'let'.  You can't write top level definitions in
> GHCi.
> 
that clears up a big mystery. one of the tutorials i read pointed out
that things are just done 'differently' in ghci, but didn't explain the
rationale as you have done.


> I hope, this helps.
>
it most certainly has!!!
thanks to you and the other write-ups here, i'm starting to see haskell
differently which will no doubt result in constructing programs
successfully.

despite the difficulties i'm having, i've been convinced this is all
worth learning. 

and without doubt, the tone and activity of this board and its people
have much to do with it!


-- 
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: 3
Date: Fri, 2 Jul 2010 09:36:47 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Re: multreplace
To: beginners@haskell.org
Cc: prad <p...@towardsfreedom.com>
Message-ID: <201007020936.48170.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

On Friday 02 July 2010 08:58:56, prad wrote:
> On Thu, 1 Jul 2010 22:31:28 -0700
>
> prad <p...@towardsfreedom.com> wrote:
> > so back to
> > the drawing board!
>
> here's what emerged:
>
> ======
> #!/usr/bin/env runghc
>
> module Main where
>
> import Useful as U
>
> main = do
>
>     let str = "This is original string"
>     let ss  = ["orig","ing"]
>     let rs  = ["very orig","ucture"]
>
>     putStrLn $ head (multRepl str ss rs)
>
>
> --multRepl :: String -> [String] -> [String] -> [String]
> multRepl [] _ _             = []
> multRepl str (s:ss) (r:rs)  = do
>     let newStr = U.replace str s r
>     if (length ss) == 0

don't do that. If you want to know whether a list is empty, use null.

if null ss
  then ...

calculating the length of a list can be very costly.

>        then return newStr
>        else multRepl newStr ss rs
> =======

What you probably want is

multRepl [] _ _ = []
multRepl str (s:ss) (r:rs) =
    let newStr = U.replace str s r
    in multRepl newStr ss rs
multRepl str _ _ = str

>
> this does produce the correct output:
> This is very original structure
>
>
> and here are my questions:
>
> 1. the type
> *Main Useful> :t multRepl
> multRepl :: (Eq t) => [t] -> [[t]] -> [[t]] -> [[t]]
>
> but i have it returning newStr which equals U.replace str s r
> and the type of U.replace is String as shown below
> *Main Useful> :t Useful.replace
> Useful.replace :: (Eq a) => [a] -> [a] -> [a] -> [a]
>
> so why is it returning [String] when newStr isn't a list of strings?

Because return in Haskell is entirely different from the return you may 
know from C/Java/...

In Haskell, return is an ordinary function with the type

return :: Monad m => a -> m a

The first equation of multRepl,

multRepl [] _ _             = []

says multRepl's result is some list type ([a], with an as yet unkown a)

later, you have

if something
  then return newStr
  else ...

newStr is a list of something (by the type of Useful.replace, newStr has 
the same type as multRepl's first argument), so, by the type of return,
multRepl's result must be have the type m ([b]) for some Monad m and some 
type b (the type of elements of str). Together with what we know from the 
first equation, it follows m = [] (indeed, [] is a Monad), so the result 
type is [[b]]

>
> 2. is the way i've done it proper haskellian? it took me quite some
> time to think this out trying to find my way through the fog of
> imperative programming.

Bad argument order.
If you had

replace pattern replacement string

you could make

multRepl pats reps = foldr (.) id (zipWith replace pats reps)

Using a higher order combinator like foldr is more haskellish than explicit 
recursion :)

>
> (my apologies for replying to my own posts - as well as my
> appreciation for your assistance)



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

Message: 4
Date: Fri, 2 Jul 2010 09:54:11 +0200
From: Daniel Fischer <daniel.is.fisc...@web.de>
Subject: Re: [Haskell-beginners] Re: multreplace
To: beginners@haskell.org
Cc: prad <p...@towardsfreedom.com>
Message-ID: <201007020954.11567.daniel.is.fisc...@web.de>
Content-Type: text/plain;  charset="iso-8859-1"

On Friday 02 July 2010 09:36:47, Daniel Fischer wrote:
> multRepl pats reps = foldr (.) id (zipWith replace pats reps)

Oops, wrong order of replacings.

We could use one of

foldr (flip (.)) id (zipWith replace pats reps)

foldr (.) id (reverse (zipWith replace pats reps)

multRepl pats reps string 
    = foldl (flip id) string (zipWith replace pats reps)

or many more.


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

Message: 5
Date: Fri, 02 Jul 2010 10:04:41 +0200
From: Heinrich Apfelmus <apfel...@quantentunnel.de>
Subject: [Haskell-beginners] Re: Enforcing Monad Laws
To: beginners@haskell.org
Message-ID: <i0k6ip$be...@dough.gmane.org>
Content-Type: text/plain; charset=UTF-8; format=flowed

Jorden M wrote:
> C++ `Concepts', which almost made it into the C++0x standard, are
> roughly similar to Haskell type classes. The proposal for concepts in
> C++ had a feature called axioms, which allow the programmer to specify
> semantics on the functions the concept contains. This allows for
> enforcing things such as the Monad Laws, as well as letting the
> compiler make certain optimizations it may not have been able to make
> without axiomatic guarantees.

I have a hard time imagining that axioms are being used to prove 
properties about programs in a language such as C++... :) Any pointers?

> Why does Haskell not have a similar
> functionality in its type classes? Was there not time, desire, etc.?
> Or are there technical limitations?

If you want to exploit algebraic identities like, say,

     map f . map g = map (f . g)

for program optimization, you can use the RULE pragma in GHC.

If you want to use the axioms to prove your program correct, you are 
beginning to leave the scope of Haskell. Have a look at dependently 
typed languages and proof assistants like  Agda  and  Coq . For 
instance, the latter can extract Haskell programs from proofs.

That being said, enforcing invariants in the types, using quickcheck and 
good old pen & paper calculations can carry you a long way towards 
program correctness in Haskell.


Regards,
Heinrich Apfelmus

--
http://apfelmus.nfshost.com



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

Message: 6
Date: Fri, 2 Jul 2010 13:33:44 +0200
From: edgar klerks <edgar.kle...@gmail.com>
Subject: Re: [Haskell-beginners] Re: the role of assignments
To: prad <p...@towardsfreedom.com>
Cc: beginners@haskell.org
Message-ID:
        <aanlktim8lma46-lqzldlz-63emihjvc5k4pvakia1...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

He Prad,


 do line <- getLine
    putStr "You entered: "
    putStrLn line

The example of Ertugrul is desugared to the following:

getLine >>= \x -> putStr "You entered: " >> putStrLn x

or even:

getLine >>= \x -> putStr "You entered: " >>= (\_ ->  putStrLn x)


It helps a lot to not use the sugared syntax, until you know how to write
them without the sugar. That way you will grasp the concept of monads much
faster.

it is also a matter of taste, for small monadic functions I prefer the
desugared style.  For longer it becomes a bit unwieldy.

Greetings,

Edgar
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20100702/fb25b04e/attachment-0001.html

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

Message: 7
Date: Fri, 2 Jul 2010 13:53:19 +0200
From: Benjamin Edwards <edwards.b...@gmail.com>
Subject: Re: [Haskell-beginners] Re: the role of assignments
To: edgar klerks <edgar.kle...@gmail.com>
Cc: beginners@haskell.org, prad <p...@towardsfreedom.com>
Message-ID:
        <aanlktimuijxdtuajqod2ncwobzrkehsqzcoz_kfbf...@mail.gmail.com>
Content-Type: text/plain; charset="iso-8859-1"

As an aside I think when I was first starting out on the path to
understanding what the hell was going on with monads, I found  the following
blog post was very insightful:

http://blog.sigfpe.com/2006/08/you-could-have-invented-monads-and.html

Regards,
Ben
-------------- next part --------------
An HTML attachment was scrubbed...
URL: 
http://www.haskell.org/pipermail/beginners/attachments/20100702/d48e7895/attachment-0001.html

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

Message: 8
Date: Fri, 2 Jul 2010 09:16:24 -0400
From: Patrick LeBoutillier <patrick.leboutill...@gmail.com>
Subject: Re: [Haskell-beginners] Re: multreplace
To: prad <p...@towardsfreedom.com>
Cc: beginners@haskell.org
Message-ID:
        <aanlktinccep8p7zhn6xvu-kfktokg32st_ref4klx...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Hi,

> --multRepl :: String -> [String] -> [String] -> [String]

Personally I woud use a list of pairs to represent the target/replacements:

multRepl :: String -> [(String,String)] -> String

That way you are guaranteed that for each target there is a
replacement and don't need to handle the cases where both lists have
different lengths.

multRepl str srs = foldl (\acc (s,r) -> replace acc s r) str srs

or in point-free form:

multRepl = foldl (\acc (s,r) -> replace acc s r)

or more succinctly (as mentionned before):

multRepl = foldl (uncurry . replace)


Patrick





> multRepl [] _ _             = []
> multRepl str (s:ss) (r:rs)  = do
>    let newStr = U.replace str s r
>    if (length ss) == 0
>       then return newStr
>       else multRepl newStr ss rs
> =======
>
> this does produce the correct output:
> This is very original structure
>
>
> and here are my questions:
>
> 1. the type
> *Main Useful> :t multRepl
> multRepl :: (Eq t) => [t] -> [[t]] -> [[t]] -> [[t]]
>
> but i have it returning newStr which equals U.replace str s r
> and the type of U.replace is String as shown below
> *Main Useful> :t Useful.replace
> Useful.replace :: (Eq a) => [a] -> [a] -> [a] -> [a]
>
> so why is it returning [String] when newStr isn't a list of strings?
>
> 2. is the way i've done it proper haskellian? it took me quite some
> time to think this out trying to find my way through the fog of
> imperative programming.
>
> (my apologies for replying to my own posts - as well as my
> appreciation for your assistance)
>
> --
> 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
>
>
> _______________________________________________
> Beginners mailing list
> Beginners@haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
>



-- 
=====================
Patrick LeBoutillier
Rosemère, Québec, Canada


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

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


End of Beginners Digest, Vol 25, Issue 5
****************************************

Reply via email to