[Haskell-cafe] are Monads with slightly stricter types in instances still Monads?

2007-01-30 Thread Julien Oster

Hello,

The type of the monadic bind function in the Monad class is

Monad m = m a - (a - m b) - m b

Now, would it be possible to create a monad with a slightly stricter 
type, like


StrictMonat m = m a - (a - m a) - m a

and, accepting that all steps of the computation would be bound to 
operate on the same type, would this be without any undesirable 
implications?


For the sake of understanding monads better, I tried to write several 
custom monads which may or may not be useful. Among those were:


 * The Tracker Monad - tracks every result of every step of the
   sequential computation in a (normal, stricly typed) list inside
   of the monad
 * The Goto Monad - sequential computation that allows restarts of
   the computation at arbitrarily set labels within it

But Haskell doesn't like those. Rightly so, because the bind function 
would have the stricter type mentioned above.


[Otherwise the Tracker monad would have to store values of different 
types in its list and the Goto monad would encounter restarts at labels 
that process different types of the value than what has been computed so 
far. Both doesn't make sense.]


I still have to prove wether those two monads follow the monadic laws at 
all, but that's part of my exercise. But let's say they follow the laws 
(I'm pretty sure that at least the Tracker monad does), is there 
anything else that would prevent the stricter typing from being legal or 
useful? Maybe I'm missing something simple.


And would I still be able to use Haskell's do syntax? My first guess 
is yes, because it really just seems to translate into normal syntax.


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


[Haskell-cafe] beginner's problam with a monad

2006-09-03 Thread Julien Oster
Hello,

after succeeding in implementing my first monad (Counter, it increments
a counter every time a computation is performed) I though I'd try
another one and went on to implement Tracker.

Tracker is a monad where a list consisting of the result of every
computation is kept alongside the final value, kind of a computation
history. It really just serves me as an exercise to implement monads.

However, the following source code fails:

{-}

data Tracker a b = Tracker [a] b
 deriving Show

instance Monad (Tracker a) where
m = f =
let Tracker l x = m in
let Tracker l' x' = f x in
Tracker (x':l) x'
return x = Tracker [] x

bar = do
  x - Tracker [] 12
  y - return (x*2)
  z - return (y*3)
  return (z+3)

{-}

Of course, style recommendations and the like are always appreciated.

(by the way, I don't really understand why I have to type
  instance Monad (Tracker a)
instead of
  instance Monad Tracker
which may very well be the problem. If it's not, can someone tell me
anyway?)

Trying to load this piece of code leads to the following error message:

Hugs.Base :load Test.hs
ERROR Test.hs:30 - Inferred type is not general enough
*** Expression: (=)
*** Expected type : Monad (Tracker a) = Tracker a b - (b - Tracker a
c) - Tracker a c
*** Inferred type : Monad (Tracker a) = Tracker a b - (b - Tracker a
a) - Tracker a a

Why does the interpreter infer Tracker a a instead of the more general
Tracker a c?

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


Re: [Haskell-cafe] beginner's problam with a monad

2006-09-03 Thread Julien Oster
Dan Doel wrote:

 Thus, unfortunately, you won't be able to implement the general bind
 operator. To do so, you'd need to have Tracker use a list that can
 store values of heterogeneous types, which is an entire library unto
 itself (HList).

Telling me that it just won't work was one of the best answers you could
give me, because now I know that I can stop trying (well, I think I will
have a look at HList. If it's easy enough...)

Now if anyone could enlighten me about the instance Monad Tracker a
instead of instance Monad Tracker part, everything will be clear!

Thanks a lot,
Julien
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: beginner's problam with a monad

2006-09-03 Thread Julien Oster
Benjamin Franksen wrote:

 Partially applying Tracker to one argument ('T a') gives you a type
 constructor that has only one remaining 'open' argument and thus can be
 made an instance of class Monad.

Totally clear, thanks a lot (also to Keegan).

Julien

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


[Haskell-cafe] Exercise in point free-style

2006-09-01 Thread Julien Oster

Hello,

I was just doing Exercise 7.1 of Hal Daumé's very good Yet Another 
Haskell Tutorial. It consists of 5 short functions which are to be 
converted into point-free style (if possible).


It's insightful and after some thinking I've been able to come up with 
solutions that make me understand things better.


But I'm having problems with one of the functions:

func3 f l = l ++ map f l

Looks pretty clear and simple. However, I can't come up with a solution. 
Is it even possible to remove one of the variables, f or l? If so, how?


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


Re: [Haskell-cafe] Exercise in point free-style

2006-09-01 Thread Julien Oster

Julien Oster wrote:


But I'm having problems with one of the functions:

func3 f l = l ++ map f l


While we're at it: The best thing I could come up for

func2 f g l = filter f (map g l)

is

func2p f g = (filter f) . (map g)

Which isn't exactly point-_free_. Is it possible to reduce that further?

Thanks,
Julien


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


Re: [Haskell-cafe] getContents and lazy evaluation

2006-09-01 Thread Julien Oster
Duncan Coutts wrote:

Hi,

 In practise I expect that most programs that deal with file IO strictly
 do not handle the file disappearing under them very well either. At best
 the probably throw an exception and let something else clean up.

And at least in Unix world, they just don't disappear. Normally, if you
delete a file, you just delete its directory entry. If there still is
something with an open handle to it, i.e. your program, the
corresponding inode (that's basically the file itself without its name
or names) still happily exists for your seeking, reading and writing.
Then, when your program closes the file and there really is no remaining
directory entry and no other process accessing it, the inode is removed
as well.

One trick for temporary files on unix is opening a new file, immediately
deleting it but still using it to write and read data.

So no problem here.

But what happens when two processes use the same file and one process is
writing into it using lazy IO which didn't happen yet? The other process
wouldn't see its changes yet.

I'm not sure if it matters, however, since sooner or later that IO will
happen. And I believe that lazy IO still means that for one operation
actually taking place, all prior operations take place in the right
order beforehand as well, no?

As for two processes writing to the same file at the same time, very bad
things may happen anyway. Sure, lazy IO prevents doing communication
between running processes using plain files, but why would you do
something like that?

Regards,
Julien




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


Re: [Haskell-cafe] Exercise in point free-style

2006-09-01 Thread Julien Oster
Udo Stenzel wrote:

Thank you all a lot for helping me, it's amazing how quickly I received
these detailed answers!

 func2 f g l = filter f (map g l)
 func2 f g = (filter f) . (map g)  -- definition of (.)
 func2 f g = ((.) (filter f)) (map g)  -- desugaring
 func2 f = ((.) (filter f)) . map  -- definition of (.)
 func2 f = flip (.) map ((.) (filter f)) -- desugaring, def. of flip
 func2 = flip (.) map . (.) . filter   -- def. of (.), twice
 func2 = (. map) . (.) . filter-- add back some sugar

Aaaah. After learning from Neil's answer and from @pl that (.) is just
another infix function, too (well, what else should it be, but it wasn't
clear to me) I still wasn't able to come up with that solution without
hurting my brain. The desugaring was the bit that was missing. Thanks, I
will keep that in mind for other infix functions as well.

I tried to work it out on paper again, without looking at your posting
while doing it. I did almost the same thing, however, I did not use
flip. Instead the last few steps read:

  = ((.) (filter f)) . map  g l
  = (.)((.) . filter f)(map)  g l   -- desugaring
  = (.map)((.) . filter f)  g l -- sweeten up
  = (.map) . (.) . filter  g l  -- definition of (.)

I guess that's possible as well?

 The general process is called lambda elimination and can be done
 mechanically.  Ask Goole for Unlambda, the not-quite-serious
 programming language; since it's missing the lambda, its manual explains
 lambda elimination in some detail.  I think, all that's needed is flip,
 (.) and liftM2.

Will do, thank you!

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


Re: [Haskell-cafe] Exercise in point free-style

2006-09-01 Thread Julien Oster
Julien Oster wrote:

   = ((.) (filter f)) . map  g l
   = (.)((.) . filter f)(map)  g l -- desugaring
   = (.map)((.) . filter f)  g l   -- sweeten up
   = (.map) . (.) . filter  g l-- definition of (.)

By the way, I think from now on, when doing point-free-ifying, my
philosophy will be:

If it involves composing a composition, don't do it.

I just think that this really messes up readability.

Cheers,
Julien

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