Re: [Haskell-cafe] Re: Practical introduction to monads

2005-08-03 Thread Bulat Ziganshin
Hello Paul,

Wednesday, August 03, 2005, 2:31:05 AM, you wrote:
PM Hmm, I've had on my list to look at the source of Darcs (and Pugs) as
PM nice real-life large-scale programs. I'm not sure I'm ready yet,
PM but maybe I should see how I go...

i also recommend you Yi and my own FreeArc as examples of imperative
programs. you can find references to these and other applications
written in Haskell in famous Haskell Communities and Activities
Report. also don't skip source code of libraries, including thats
included in ghc itself 

about your first question - read 
http://www.nomaware.com/monads/monad_tutorial.zip


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Problem type checking class-method implementation

2005-08-03 Thread Stefan Holdermans

Dear Haskellers,

Yesterday I stumbled upon a problem type checking a program involving 
multi-parameter type classes. GHC rejected the program; still, I was 
not immediately convinced it contained a type error. Having given it 
some more thoughts, I start to suspect that the type checker is in err 
and that the program is well-typed after all. But, well, I might be 
overlooking something obvious...


I have reduced my code to a small but hopelessly contrived example 
program exposing the problem. Please hang on.


Because we employ multi-parameter type classes, we need the Glasgow 
extensions:


  {-# OPTIONS -fglasgow-exts #-}

Let's start easy and define the identity monad:

  newtype Identity a = Identity {runIdentity :: a}

  instance Monad Identity where
return   = Identity
Identity a = f = f a

Then, let's introduce the foundations for the (contrived) example:

  class (Monad m) = IsItem m i where
processItem :: i - m ()

  class (Monad m) = IsProcessor p m | m - p where
process :: (IsItem m i) = i - m ()
-- ...some more methods, possibly involving p...

So, an item is something that can be processed within the context of a 
certain monad, and a processor is something that can process an item of 
an appropriate type. Note the functional dependency from m to p: a 
processor type m uniquely determines the type of the processing context 
p.


Before we move on, consider this canonical item type, which is just a 
one-field record representing an implementation of the IsItem class:


  newtype Item m = Item {processItemImpl :: m ()}

The corresponding instance declaration is obvious:

  instance (Monad m) = IsItem m (Item m) where
processItem = processItemImpl

Furthermore values of every type that is an instance of IsItem can be 
converted to corresponding Item values:


  toItem :: (IsItem m i) = i - Item m
  toItem =  Item . processItem

Please stick with me, for we are now going to implement a monad 
transformer for processors (which, for this example, is really just the 
identity monad transformer):


  newtype ProcessorT p m a = ProcessorT {runProcessorT :: m a}

  instance (Monad m) = Monad (ProcessorT p m) where
return = ProcessorT . return
ProcessorT m = f = ProcessorT (m = runProcessorT . f)

  instance (Monad m) = IsProcessor p (ProcessorT p m) where
process = processItem

Then, finally, we use this transformer to derive a processor monad:

  newtype Processor p a = Processor {unwrap :: ProcessorT p Identity a}

  runProcessor :: Processor p a - a
  runProcessor =  runIdentity . runProcessorT . unwrap

So, we just make sure that Processor is a monad:

  instance Monad (Processor p) where
return= Processor . return
Processor m = f = Processor (m = unwrap . f)

Now all what is left to do is declare Processor an instance of 
IsProcessor. To this end, we need to be able to cast items for 
Processor p to items for ProcessorT p Identity (for all p). The 
following function takes care of that:


  castItem :: (IsItem (Processor p) i) = i - Item (ProcessorT p 
Identity)

  castItem =  Item . unwrap . processItem

Note that up 'til now everything is fine: GHC is happy, I am happy. But 
then,
when all the hard work is done, and we just only have to connect things 
properly, it just breaks:


  instance IsProcessor p (Processor p) where
process = Processor . process . castItem

After adding this last instance declaration, GHC happily reports:

  Processor.hs:56:24:
Could not deduce (IsItem (ProcessorT p Identity)
 (Item (ProcessorT p1 Identity)))
  from the context (IsProcessor p (Processor p),
Monad (Processor p),
IsItem (Processor p) i)
  arising from use of `process' at Processor.hs:56:24-30
Probable fix:
  add (IsItem (ProcessorT p Identity) (Item (ProcessorT p1 
Identity)))

  to the class or instance method `process'
  or add an instance declaration for
(IsItem (ProcessorT p Identity)
(Item (ProcessorT p1 Identity)))
In the first argument of `(.)', namely `process'
In the second argument of `(.)', namely `process . castItem'
In the definition of `process': process = Processor . (process . 
castItem)


  Processor.hs:56:34:
Could not deduce (IsItem (Processor p1) i)
  from the context (IsProcessor p (Processor p),
Monad (Processor p),
IsItem (Processor p) i)
  arising from use of `castItem' at Processor.hs:56:34-41
Probable fix:
  add (IsItem (Processor p1) i) to the class or instance method 
`process'

  or add an instance declaration for (IsItem (Processor p1) i)
In the second argument of `(.)', namely `castItem'
In the second argument of `(.)', namely `process . castItem'
In the definition of `process': process = Processor . (process . 
castItem)


It seems to me that the type checker fails to 

Re: [Haskell-cafe] Practical introduction to monads

2005-08-03 Thread yoann padioleau


On 2 août 05, at 22:03, Paul Moore wrote:


I've started learning Haskell, and I'm going through all the tutorial
material I can find - there's a lot of good stuff available.

One thing I haven't found a really good discussion of, is practical
examples of building monads. There's plenty of discussion of the IO
monad, and the state monad, and a lot of good theory on monads, but
although I've seen tantalising statements about how powerful the
ability to define your own monads can be, but no really concrete
examples - something along the lines of

  - here is problem X
  - this might be our first cut at coding it
  - we can abstract out this stuff, as a monad
  - see how the code looks now, how much cleaner it is

(I've seen this type of model developing a state monad, but I'm
looking for a more application-specific approach).


have you read this
  http://homepages.inf.ed.ac.uk/wadler/papers/marktoberdorf/ 
marktoberdorf.pdf ?
It presents a pb, show how it sux when coded naively without monad,  
and then show

how beautiful the code is when you use a monad.

I have also one time read an example where you use monads while
implementing the unification or type inference algorithm, perhaps in  
the original

monad paper (the essence of functional programming).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Practical introduction to monads

2005-08-03 Thread Stefan Holdermans

Yoann,


I have also one time read an example where you use monads while
implementing the unification or type inference algorithm, perhaps in 
the original

monad paper (the essence of functional programming).


I guess you are referring to Mark Jones' _Functional Programming with 
Overloading and Higher-order Polymorphism_ [1].


Cheers,

Stefan

http://www.cs.uu.nl/~stefan/

  [1] Mark P. Jones. Functional programming with overloading and 
higher-order polymorphism. In Johan Jeuring and Erik Meijer, editors, 
Advanced Functional Programming, First International Spring School on 
Advanced Functional Programming Techniques, Bastad, Sweden, May 24–30, 
1995, Tutorial Text, volume 925 of Lecture Notes in Computer Science, 
pages 97–136. Springer-Verlag, 1995.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Problem type checking class-method implementation

2005-08-03 Thread Ralf Lammel
Stefan,

the problem can be spotted in the following erased version of your
program.

data Identity a

instance Monad Identity

class (Monad m) = IsItem m i where
  processItem :: i - m ()

class (Monad m) = IsProcessor p m | m - p where
  process :: (IsItem m i) = i - m ()

newtype Item m = Item {processItemImpl :: m ()}

newtype ProcessorT p m a = ProcessorT {runProcessorT :: m a}

instance (Monad m) = Monad (ProcessorT p m)
  
instance (Monad m) = IsProcessor p (ProcessorT p m)

newtype Processor p a = Processor {unwrap :: ProcessorT p Identity a}

instance Monad (Processor p) where

castItem :: (IsItem (Processor p) i) = i - Item (ProcessorT p
Identity)
castItem = undefined

instance IsProcessor p (Processor p) where
  process = Processor . process . castItem

Recall the type error:

Could not deduce (IsItem (Processor p1) i)
  from the context (IsProcessor p (Processor p),
Monad (Processor p),
IsItem (Processor p) i)


The problem is basically in here:

instance IsProcessor p (Processor p) where
  process = Processor . process . castItem

By specializing function signatures according to the instance head,
and by applying type checking constraints for functional composition,
we get these types:

Processor :: ProcessorT p Identity () - Processor p ()

process :: process :: ( IsProcessor p (ProcessorT p Identity)
  , IsItem (ProcessorT p1 Identity) ()
  )
= Item (ProcessorT p1 Identity)
- ProcessorT p Identity ()

castItem :: (IsItem (Processor p1) i) =
i - Item (ProcessorT p1 Identity)

The problem is the type-scheme polymorphic result type of
castItem which is consumed by a type-variable polymorphic 
but type-class bounded argument type of process.

The constraint of this application process, i.e.,
IsItem (Processor p1) i
is the one GHC asks for.

(Do the hugs test :-))

Ralf


 -Original Message-
 From: [EMAIL PROTECTED] [mailto:haskell-cafe-
 [EMAIL PROTECTED] On Behalf Of Stefan Holdermans
 Sent: Wednesday, August 03, 2005 1:01 AM
 To: haskell-cafe
 Subject: [Haskell-cafe] Problem type checking class-method
implementation
 
 Dear Haskellers,
 
 Yesterday I stumbled upon a problem type checking a program involving
 multi-parameter type classes. GHC rejected the program; still, I was
 not immediately convinced it contained a type error. Having given it
 some more thoughts, I start to suspect that the type checker is in err
 and that the program is well-typed after all. But, well, I might be
 overlooking something obvious...
 
 I have reduced my code to a small but hopelessly contrived example
 program exposing the problem. Please hang on.
 
 Because we employ multi-parameter type classes, we need the Glasgow
 extensions:
 
{-# OPTIONS -fglasgow-exts #-}
 
 Let's start easy and define the identity monad:
 
newtype Identity a = Identity {runIdentity :: a}
 
instance Monad Identity where
  return   = Identity
  Identity a = f = f a
 
 Then, let's introduce the foundations for the (contrived) example:
 
class (Monad m) = IsItem m i where
  processItem :: i - m ()
 
class (Monad m) = IsProcessor p m | m - p where
  process :: (IsItem m i) = i - m ()
  -- ...some more methods, possibly involving p...
 
 So, an item is something that can be processed within the context of a
 certain monad, and a processor is something that can process an item
of
 an appropriate type. Note the functional dependency from m to p: a
 processor type m uniquely determines the type of the processing
context
 p.
 
 Before we move on, consider this canonical item type, which is just a
 one-field record representing an implementation of the IsItem class:
 
newtype Item m = Item {processItemImpl :: m ()}
 
 The corresponding instance declaration is obvious:
 
instance (Monad m) = IsItem m (Item m) where
  processItem = processItemImpl
 
 Furthermore values of every type that is an instance of IsItem can be
 converted to corresponding Item values:
 
toItem :: (IsItem m i) = i - Item m
toItem =  Item . processItem
 
 Please stick with me, for we are now going to implement a monad
 transformer for processors (which, for this example, is really just
the
 identity monad transformer):
 
newtype ProcessorT p m a = ProcessorT {runProcessorT :: m a}
 
instance (Monad m) = Monad (ProcessorT p m) where
  return = ProcessorT . return
  ProcessorT m = f = ProcessorT (m = runProcessorT . f)
 
instance (Monad m) = IsProcessor p (ProcessorT p m) where
  process = processItem
 
 Then, finally, we use this transformer to derive a processor monad:
 
newtype Processor p a = Processor {unwrap :: ProcessorT p Identity
a}
 
runProcessor :: Processor p a - a
runProcessor =  runIdentity . runProcessorT . unwrap
 
 So, we just make sure that Processor is a monad:
 
instance Monad (Processor p) where
  return  

Re: [Haskell-cafe] Problem type checking class-method implementation

2005-08-03 Thread Stefan Holdermans

Ralf,


The problem is the type-scheme polymorphic result type of
castItem which is consumed by a type-variable polymorphic
but type-class bounded argument type of process.


Thanks for your explanation: I hope it's still safe to say that I did 
not miss something entirely obvious. :) Anyway, indeed, I do see 
bubbling that one type-class constraint to the top-level.


So, playing around, rewriting things just a little, I end up with

  instance IsProcessor p (Processor p) where
process = Processor . unwrap . processItem

which is disappointingly the most obvious implementation anyway. 
Disappointingly, however, because it equivalent to what I had written 
in the original program, i.e., the one that brought me to consider all 
this in the first place. And there, for some reason, it did not work 
and led me to the deviation via (something equivalent to) castItem. 
Well, that's what you get from simplifying stuff. Anyway, it seems time 
to have another look at the original program and maybe come with 
another type-checking puzzle later. ;)


Thanks,

Stefan

http://www.cs.uu.nl/~stefan/

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Thread pool in GHC

2005-08-03 Thread Dinh Tien Tuan Anh


 Can thread pool be implemented in GHC ?

I have a program that is currently using about 12-15 threads (launch and 
kill for infinite times) and when running, especially after Ctrl-C, my 
computer got freezed up. And if i ran it several times, the Stack 
overflows occurs.


Cheers
TuanAnh

_
Winks  nudges are here - download MSN Messenger 7.0 today! 
http://messenger.msn.co.uk


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Thread pool in GHC

2005-08-03 Thread Sebastian Sylvan
On 8/4/05, Dinh Tien Tuan Anh [EMAIL PROTECTED] wrote:
 
   Can thread pool be implemented in GHC ?
 
 I have a program that is currently using about 12-15 threads (launch and
 kill for infinite times) and when running, especially after Ctrl-C, my
 computer got freezed up. And if i ran it several times, the Stack
 overflows occurs.
 

Did you try -threaded ?

-- 
Sebastian Sylvan
+46(0)736-818655
UIN: 44640862
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe