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:  Meaning of variable' (Bas van Dijk)
   2.  untilM and scanM (Jan Snajder)
   3.  Type question (Paul Johnston)
   4. Re:  Type question (Yitzchak Gale)
   5. Re:  Type question (Brandon S. Allbery KF8NH)
   6.  Problems inferring instances (dcmorse+hask...@gmail.com)
   7. Re:  Problems inferring instances (Dave Bayer)
   8. Re:  Problems inferring instances (Brandon S. Allbery KF8NH)
   9.  Re: Yet another monad tutorial. (Benjamin L.Russell)


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

Message: 1
Date: Mon, 5 Jan 2009 13:42:41 +0100
From: "Bas van Dijk" <v.dijk....@gmail.com>
Subject: Re: [Haskell-beginners] Meaning of variable'
To: Beginners@haskell.org
Message-ID:
        <f73f66150901050442uff27476y8040ae25e6f8f...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

On Sun, Jan 4, 2009 at 6:55 AM, Brandon S. Allbery KF8NH
<allb...@ece.cmu.edu> wrote:
> On 2009 Jan 4, at 0:52, Erik de Castro Lopo wrote:
>>
>>   function' = .....
>>
>> What does the tick mean??
>
>
> By convention it signals a variant of the function without the tick...

The tick is often used to signal a more strict variant of the function
without the tick.

See foldl and foldl' for example:

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

regards,

Bas


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

Message: 2
Date: Mon, 05 Jan 2009 14:16:11 +0100
From: Jan Snajder <jan.snaj...@fer.hr>
Subject: [Haskell-beginners] untilM and scanM
To: beginners@haskell.org
Message-ID: <1231161371.5829.74.ca...@arjuna>
Content-Type: text/plain

Hi,

is there a reason why there is no monadic version of "until" in the
Haskell libraries? It would be defined as follows:

untilM :: (Monad m) => (a -> Bool) -> (a -> m a) -> a -> m a
untilM p f x | p x       = return x
             | otherwise = f x >>= untilM p f

The same applies to scanM, also not part of the libraries:

scanM :: (Monad m) => (a -> b -> m a) -> a -> [b] -> m [a]
scanM f q [] = return [q]
scanM f q (x:xs) =
   do q2 <- f q x
      qs <- scanM f q2 xs
      return (q:qs)

I often find myself in need for these. To me these seem idiomatic enough
to be included in the library. But since they is not, I guess there must
be another, more idiomatic way to do this.

Thank you,
Jan



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

Message: 3
Date: Mon, 05 Jan 2009 20:40:56 +0000
From: Paul Johnston <paul.a.johns...@manchester.ac.uk>
Subject: [Haskell-beginners] Type question
To: Haskell <beginners@haskell.org>
Message-ID: <49627058.5010...@manchester.ac.uk>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

Hi, I was playing around after getting the new O'Reilly book with lists 
and their operators!
Not sure what the below actually means?

Prelude> [] : []
[[]]
it :: [[a]]

(Got :set +t on )

I thought the first argument of ':' must be an element, so is the empty 
list an element of the same type of the contents of the empty list?

Yours confused Paul :-)





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

Message: 4
Date: Tue, 6 Jan 2009 00:52:43 +0200
From: "Yitzchak Gale" <g...@sefer.org>
Subject: Re: [Haskell-beginners] Type question
To: "Paul Johnston" <paul.a.johns...@manchester.ac.uk>
Cc: Haskell <beginners@haskell.org>
Message-ID:
        <2608b8a80901051452g17100fa9qe8b37919e1ec0...@mail.gmail.com>
Content-Type: text/plain; charset=ISO-8859-1

Hi Paul,

You wrote:
> Prelude> [] : []
> [[]]
> it :: [[a]]
> I thought the first argument of ':' must be an element, so is the empty list
> an element of the same type of the contents of the empty list?

There is not just one "empty list". The symbol [] is actually
polymorphic - it can refer to the empty list in [a], for any type a.

In particular, "a" can itself be a list type. So [] : [] is an element
of [[a]], the type of list of lists of a, for any type a.

Hope this helps,
Yitz


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

Message: 5
Date: Mon, 5 Jan 2009 17:53:21 -0500
From: "Brandon S. Allbery KF8NH" <allb...@ece.cmu.edu>
Subject: Re: [Haskell-beginners] Type question
To: Paul Johnston <paul.a.johns...@manchester.ac.uk>
Cc: Haskell <beginners@haskell.org>
Message-ID: <ed11d725-86ef-4f12-9262-0d8274b84...@ece.cmu.edu>
Content-Type: text/plain; charset=US-ASCII; format=flowed; delsp=yes

On 2009 Jan 5, at 15:40, Paul Johnston wrote:
> Hi, I was playing around after getting the new O'Reilly book with  
> lists and their operators!
> Not sure what the below actually means?
>
> Prelude> [] : []
> [[]]
> it :: [[a]]
>
> (Got :set +t on )
>
> I thought the first argument of ':' must be an element, so is the  
> empty list an element of the same type of the contents of the empty  
> list?


(:) :: a -> [a] -> [a]

In this case the first argument is an empty list (type forall a. [a])  
and the second must therefore be an empty list of lists (type forall  
a. [[a]]).  Hence the result is also of type forall a. [[a]] (with all  
the `a's unified).

-- 
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university    KF8NH




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

Message: 6
Date: Mon, 05 Jan 2009 21:40:36 -0500
From: dcmorse+hask...@gmail.com
Subject: [Haskell-beginners] Problems inferring instances
To: beginners@haskell.org
Message-ID: <e1lk1rw-0006ag...@abu.osaurus.us>

Learning from the example of "read" and also Real World Haskell, I
come across the idea to overload my function's return types. Trying to
think of an application for this, I've always wanted to write ==
applications like in Icon, that is

a === b === c means a == b && b == c.

This requires === to sense what context it is called in. If it's being
called for a Boolean value, it needs to return a Boolean value. If
it's being called as a parameter to another === application, then it
needs to somehow remember both it's truthiness and if true what value
its already seen.

The idea is to eventually expand this to be able to write

a >== b >== c

...but one thing at a time!

My plan of attack is to write a typeclass:
class Chain a b c where
 (==) :: a -> b -> c
First check: Turned on -fglasgowexts to allow multiple parameters to
typeclasses.


Then write instances for the various contexts in which == might be
applied. For boolean return values there are three instances:

instance Eq a => Chain a a Bool ...
 example: 5 == 4
instance Eq a => Chain (Valid a) a Bool
 example:  rightmost == in (5==4)==3
instance Eq a => Chain a (Valid a) Bool
 example: leftmost == in 5==(4==3)

 Sidebar: Valid is just an imitation of Maybe:
 data Valid a = Value a | Fail deriving (Show)

But back to ==, the interesting part is the times when one senses
we're in a context of comparing more values, for example, the left ==
in (x==y)==z.

instance Eq a => Chain a a (Valid a)
instance Eq a => Chain (Valid a) a (Valid a)
instance Eq a => Chain a (Valid a) (Valid a)

To test out this implementation I write a test function:
test2 :: Eq a => a -> a -> Bool
test2 a b = a === b
and this works as expected.

The problem comes when chainging the ===s together, I have to
spoon-feed the compiler the inferred type:


-- compiling this causes an error
test3choke :: Eq a => a -> a -> a -> Bool
test3choke a b c = a === b === c

The error text:

 [1 of 1] Compiling ME               ( ME.hs, interpreted )

 ME.hs:63:19:
     Could not deduce (Chain a a c) from the context (Eq a)
       arising from use of `===' at ME.hs:63:19-25
     Possible fix:
       add (Chain a a c) to the type signature(s) for `test3choke'
     In the first argument of `(===)', namely `a === b'
     In the expression: (a === b) === c
     In the definition of `test3choke':
         test3choke a b c = (a === b) === c

 ME.hs:63:19:
     Could not deduce (Chain c a Bool) from the context (Eq a)
       arising from use of `===' at ME.hs:63:19-31
     Possible fix:
       add (Chain c a Bool) to the type signature(s) for `test3choke'
       or add an instance declaration for (Chain c a Bool)
     In the expression: (a === b) === c
     In the definition of `test3choke':
         test3choke a b c = (a === b) === c
 Failed, modules loaded: none.


-- but spoon-feeding it the types will work
test3Int  :: Int -> Int -> Int -> Bool
test3Int  a b c = ((a === b) :: Valid Int) === c

So it seems that the compiler is not doing instance inference the same
way it does type inference. This is frustrating because the output of
the parenthesiszed a === b can only be either of type Bool or Valid a,
and the second argument of the outer === has to have the same type,
which will force it to Valid a in most cases (Bool being an
interesting exception).

Is there some way to goad the compiler forward on this one, or is this
the wrong approach altogether?

Attachment: http://www.osaurus.us/~dm/tmp/ME.hs


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

Message: 7
Date: Mon, 5 Jan 2009 19:24:13 -0800
From: Dave Bayer <ba...@cpw.math.columbia.edu>
Subject: Re: [Haskell-beginners] Problems inferring instances
To: dcmorse+hask...@gmail.com
Cc: beginners@haskell.org
Message-ID: <f07f9a86-1fcb-460e-bcea-51cb475d1...@math.columbia.edu>
Content-Type: text/plain; charset=US-ASCII; format=flowed; delsp=yes

Here's a very indirect answer, more a hunch:

I'm not sure how, but what you're trying to do reminds me of  
Control.Applicative. Go take a look at the documentation and/or source  
code for that library, then follow the link to

        Applicative Programming with Effects
        Conor McBride and Ross Paterson
        http://www.soi.city.ac.uk/~ross/papers/Applicative.html

which is one of the most beautiful papers ever written on Haskell.  
Even if I'm sending you on a wild goose chase, you'll enjoy the paper.

I've had similar monumental struggles trying to push the type system  
past my understanding of how it works. I find that invariably, if I  
roll back one click on my ambitions, type "darcs revert", step outside  
for 30 seconds, then what I want to do works without incident on the  
next try. A good example of this is the "wrapper" class Sum in  
Data.Monoid. You'd think that one could just tell the type system that  
a Num is a Monoid, but the type system _really_ likes something to  
chew on, hence the wrapper. I spent way too long contemplating GHC  
error messages proposing the option -XLetGravityFailButDontBlameUs,  
before accepting that if there was a better way, it would be in the  
library code.

So the key to maintaining momentum as a Haskell beginner is to see the  
simplification, one-click compromise that makes your obstacle trivial.  
Here, if I were you I'd first write your code for practice with the  
left- (or right-?) most === a different operator. By analogy with  
Applicative, or with the . . . . $ pattern one sees everywhere when  
composing. Then maybe it will be clear how to write it the way you want.

On Jan 5, 2009, at 6:40 PM, dcmorse+hask...@gmail.com wrote:

> Learning from the example of "read" and also Real World Haskell, I
> come across the idea to overload my function's return types. Trying to
> think of an application for this, I've always wanted to write ==
> applications like in Icon, that is
>
> a === b === c means a == b && b == c.


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

Message: 8
Date: Mon, 5 Jan 2009 22:53:07 -0500
From: "Brandon S. Allbery KF8NH" <allb...@ece.cmu.edu>
Subject: Re: [Haskell-beginners] Problems inferring instances
To: dcmorse+hask...@gmail.com
Cc: beginners@haskell.org
Message-ID: <ee22d117-abeb-4583-a4c8-6a8cf1047...@ece.cmu.edu>
Content-Type: text/plain; charset=US-ASCII; format=flowed; delsp=yes


On 2009 Jan 5, at 21:40, dcmorse+hask...@gmail.com wrote:

> Learning from the example of "read" and also Real World Haskell, I
> come across the idea to overload my function's return types. Trying to
> think of an application for this, I've always wanted to write ==
> applications like in Icon, that is
>
> a === b === c means a == b && b == c.
>
> This requires === to sense what context it is called in. If it's being
> called for a Boolean value, it needs to return a Boolean value. If
> it's being called as a parameter to another === application, then it
> needs to somehow remember both it's truthiness and if true what value
> its already seen.

My thought is that Icon's notion of failure as an out-of-band result  
is best captured by the Monad instance for Maybe (or, perhaps more  
generally, MonadZero or whatever we're going to call it this time  
around; at the moment that means Monad).  Unfortunately, this can't be  
made especially clean:  given

 > (<==) :: Eq a => a -> a -> m Bool
 > a <== b = if a <= b then b else fail ">"

which causes -1 <== x <== 1 (say) to do the right thing, you have to  
either escape the monad to use it as a comparison or create a lifted  
if-then-else.

-- 
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] allb...@kf8nh.com
system administrator [openafs,heimdal,too many hats] allb...@ece.cmu.edu
electrical and computer engineering, carnegie mellon university    KF8NH




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

Message: 9
Date: Tue, 06 Jan 2009 21:09:07 +0900
From: Benjamin L.Russell <dekudekup...@yahoo.com>
Subject: [Haskell-beginners] Re: Yet another monad tutorial.
To: beginners@haskell.org
Message-ID: <gnf6m45b269m7atr9uvi6baivn3fsgp...@4ax.com>
Content-Type: text/plain; charset=iso-2022-jp

On Mon, 5 Jan 2009 09:08:37 -0200, "Rafael Gustavo da Cunha Pereira
Pinto" <rafaelgcpp.li...@gmail.com> wrote:

>Hello everyone
>
>
>I am a very eclectic person when it comes to computer languages, and I found
>this monad tutorial for OCaml programmers:
>
>http://enfranchisedmind.com/blog/2007/08/06/a-monad-tutorial-for-ocaml/
>
>I found it to be very interesting, since it shows those "warm, fuzzy things"
>implemented in another functional language with very clear explanations of
>what he is doing in each step.
>
>Best regards, and a happy 2k9 for you all!
>
>Rafael

>From the aforementioned monad tutorial for O'Caml programmers:

>A ‘newbie’, in Haskell, is someone who hasn’t yet 
>implemented a compiler. They’ve only written a monad tutorial.
>    -Pseudonymn

Fascinating.

>Forget category theory. Forget space suits and free will and all the other bad 
>analogies floating around about Monads. 
>Monads are first and foremost a design pattern, as in the Gang of Four 
>“Design Patterns” book. 

An interesting perspective.  The focus on design patterns brings to
mind the book How to Design Programs (see http://www.htdp.org/), by
Felleisen, Findler, Flatt, and Krishnamurthi, on Scheme, and the
recent dialect of Typed Scheme (see
http://www.ccs.neu.edu/home/samth/typed-scheme/), as well as the
language Qi (see http://www.lambdassociates.org/whatsnew.htm).

There is a somewhat similar tutorial on monads using Qi (see
"Programming Kung Fu Qi: Monads in Qi" at
http://programmingkungfuqi.blogspot.com/2007/02/monads-in-qi.html).

For reference, I shall use the Haskell-based monad tutorial "All About
Monads" (see http://www.haskell.org/all_about_monads/html/index.html)
as a base for one of the Haskell versions of the examples.  Most of my
descriptions of the Haskell version will be borrowed from the
descriptions contained in the section there entitled "Meet the Monads"
(see http://www.haskell.org/all_about_monads/html/meet.html).

Let's compare the Haskell version with the O'Caml version and a
hypothetical pure Scheme version:

Haskell version of monad rules (borrowed from the Qi-based tutorial
(not the Haskell one)):
>class Monad m where
>   return :: a -> m a
>   (>>=)  :: m a -> (a -> m b) -> m b

O'Caml version of monad rules (borrowed from the O'Caml-based
tutorial):
>module type MonadRequirements = sig
>    type ‘a t
>    val bind : ‘a t -> (’a -> ‘b t) -> ‘b t
>    val return : ‘a -> ‘a t
>end;;

Hypothetical pure Scheme version of monad rules (borrowed from the
Qi-based tutorial):
>   (pipe (lift x) f)   = (f x)
>   (pipe m lift)       = m
>   (pipe (pipe m f) g) = (pipe m (lambda (x) (pipe (f x) g))

The Haskell version is the most concise.  The "return" and "(>>=)"
("bind") operations in Haskell correspond to the "return" and "bind"
operations in the O'Caml version, and to the "lift" and "pipe"
operations in the hypothetical pure Scheme version.

In the Haskell version, "m" is the type constructor, "return" is an
operation that creates a value of the monad type "m a," while "(>>=)"
(a.k.a. "bind") is an operation that combines a value of that type "m
a" with a computation that produces values of that type to produce a
new computation for values of that type "(a -> m b) -> m b."

Superficially, so far, the three versions seem fairly equivalent to
me.

Now for examples of list monads:

Haskell version (adapted from combining the Haskell-based and the
Qi-based tutorials):
>instance Monad [ ] where
>   l >>= f = concatMap f l
>   []     >>= f = []
>   return x     = [x]

Your O'Caml version (borrowed from the O'Caml-based tutorial):
>module ListMonad = struct
>    type ‘a t = ‘a list;;
>
>    let bind lst f = List.concat (List.map f lst);;
>
>    let return x = [ x ];;
>end;;

Qi version (borrowed from the Qi-based tutorial):
>(define bind
>   [] _ -> []
>   [X | Xs] F -> (append (F X) (bind Xs F)))
>
>(define return
>   X -> [X]  )

Here we start to see some differences.

In the Haskell version, "return" simply creates a singleton list
("[x]"), while "(>>=)" (i.e., "bind") either returns a blank list "[]"
in the case of a blank list, or otherwise creates a new list
containing the results of applying the function to all of the values
in the original list "concatMap f l."

In the O'Caml version, notice the "List.concat" operation.  After the
List.map operation, we are left with not a "‘a list", but instead
with a "‘a list list", so this is necessary to obtain the correct
type "‘a list."  Otherwise, the reasoning is similar.

In the Qi version, we have split the monad into two functions:  "bind"
and "return."  Splitting a large function into a smaller functions is
typical Scheme style.  Here, "return" simply pattern-matches an
element into a list containing that element, while "bind" either
pattern-matches an empty list "[]" following by anything "_" to an
empty list "[]," or pattern-matches a list consisting of a car and a
cdr "[X | Xs]," followed by a function "F," to "F" applied to "X,"
which is "(F X)," appended to a binding of the cdr of the list "Xs" to
the function "F."

It seems that studying the Qi version may shed some insight into the
Haskell version by approaching it from a different perspective.  This
may also be true of the O'Caml version, but personally, I think that
the splitting of the monad into separate functions for "bind" and
"return" in the Qi version helps to differentiate it from the other
two versions, and hence offers additional insight into the nature of
the monad.

It may also be said that the use of both "List.map" and "List.concat"
in the O'Caml version offers similar insight.

Now for a pet peeve that I have with one of the examples in the O'Caml
monad tutorial:

>module SerialMonad = struct
>    type ‘a t = unit -> ‘a;;
>    let serial_mutex = Mutex.create ();;
>    let return x = (fun () -> x);;
>    let bind m g = (fun () -> (g (m ())) ());;
>    let access m =
>        Mutex.lock serial_mutex;
>        try
>            let r = m () in
>            Mutex.unlock serial_mutex;
>            r
>        with
>        | e ->
>            begin
>                Mutex.unlock serial_mutex;
>                raise e
>            end
>end;;
>
>This monad is basically identical to the previous FunMonad with the addition 
>of the access function- which executes the 
>process while holding the serial_mutex lock, which is always unlocked when the 
>process completes (even if the process 
>throws an exception). This forces all processes executing within a SerialMonad 
>to be executed sequentially and serially 
>(thus the name).

While a clear example, one problem that I have with this approach is
that the emphasis on forcing "all processes executing within a
SerialMonad to be executed sequentially and serially" reminds me of
the Imperative Way.  This brings to mind a posting by Paul Hudak on
Haskell-Cafe, entitled "a regressive view of support for imperative
programming in Haskell," dated "Wed Aug 8 14:20:39 EDT 2007" (see
http://www.haskell.org/pipermail/haskell-cafe/2007-August/030178.html),
in which he writes as follows:

>In my opinion one of the key principles in the design of Haskell has 
>been the insistence on purity.  It is arguably what led the Haskell 
>designers to "discover" the monadic solution to IO, and is more
>generally what inspired many researchers to "discover" purely functional 
>solutions to many seemingly imperative problems.  With references and 
>mutable data structures and IO and who-knows-what-else to support the 
>Imperative Way, this discovery process becomes stunted.
>
>Well, you could argue, monad syntax is what really made Haskell become 
>more accepted by the masses, and you may be right (although perhaps 
>Simon's extraordinary performance at OSCOM is more of what we need).  On 
>the other hand, if we give imperative programmers the tools to do all 
>the things they are used to doing in C++, then we will be depriving them 
>of the joys of programming in the Functional Way.  How many times have 
>we seen responses to newbie posts along the lines of, "That's how you'd 
>do it in C++, but in Haskell here's a better way...".

Although I greatly applaud alternative perspectives in learning
Haskell, I am somewhat suspicious of the emphasis on a
quasi-imperative approach.  One of the factors that initially
attracted me to Haskell in the first place was the emphasis on a
functional style.  In particular, purely functional code has a number
of advantages, including easier reasoning about program behavior,
easier formulation of proofs of correctness, and referential
transparency. Together with referential transparency comes
applicativity of formal methods of program analysis.  All this is lost
once the Functional Way is replaced by the Imperative Way.

Here, the Qi-based monad tutorial seems to focus more on examples that
use the functional approach, but perhaps this is just my opinion.

Comparative programming languages can be a very interesting topic.  If
anybody knows of any alternative monad tutorials in other functional
programming languages that could help to shed light on monads, please
feel free to mention them in this thread.

-- Benjamin L. Russell
-- 
Benjamin L. Russell  /   DekuDekuplex at Yahoo dot com
http://dekudekuplex.wordpress.com/
Translator/Interpreter / Mobile:  +011 81 80-3603-6725
"Furuike ya, kawazu tobikomu mizu no oto." 
-- Matsuo Basho^ 
-- 
Benjamin L. Russell  /   DekuDekuplex at Yahoo dot com
http://dekudekuplex.wordpress.com/
Translator/Interpreter / Mobile:  +011 81 80-3603-6725
"Furuike ya, kawazu tobikomu mizu no oto." 
-- Matsuo Basho^ 



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

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


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

Reply via email to