Re: [Haskell-cafe] Re: A free monad theorem?

2006-09-01 Thread Andrea Rossato
Il Fri, Sep 01, 2006 at 07:22:02AM +0200, Tomasz Zielonka ebbe a scrivere:
 On Fri, Sep 01, 2006 at 01:13:14AM +0200, Benjamin Franksen wrote:
  So getting the value out of the monad is not a pure function (extract ::
  Monad m = m a - a). I think I stated that, already, in my previous post.
 
 The only generic way of extracting values from a monadic value is
 the bind operator. The lack of extract function is a feature :-)
 But now I know that you are not really claiming such a function exists.

I do not understand this discussion, but I'd like to.

Can you please tell me what you are talking about in terms of this
example?
Thanks,
Andrea

module Test where

newtype M a = TypeConstructor {unpack::(a, String)}
deriving (Show)

instance Monad M where
return a = (TypeConstructor (a,))
(=) m f = TypeConstructor (a1,b++b1)
where (a,b) = unpack m
  (a1,b1) = unpack (f a)

putB b = TypeConstructor ((),b)
putA a = (TypeConstructor (a,))
getA (TypeConstructor (a,b)) = a
getB (TypeConstructor (a,b)) = b

transformM :: Int - M Int
transformM a = do putA 3
  putB ciao
  putA 6
  putB  cosa?
  return 4

{-
*Test let a = transformM 1
*Test a
TypeConstructor {unpack = (4,ciao cosa?)}
*Test getA a
4
*Test getB a
ciao cosa?
*Test 
-}
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] state and exception or types again...

2006-09-01 Thread Bulat Ziganshin
Hello Andrea,

Thursday, August 31, 2006, 4:22:49 PM, you wrote:

 The tutorial will have this outline: first we build a monad adding
 output, exception, and state. Then we use monad transformer to take
 out state and output and add debug, doing lifting, put(ing) and
 get(ing) by hand, to understand the central role of type
 matching/construction.

imho, your tutorial makes the error that is a very typical: when you
write your tutorial you already know what are monads and what the
program you will construct at the end. but your reader don't know all these!
for such fresh reader this looks as you made some strange steps, write
some ugly code and he don't have chances to understand that this ugly
code is written just to show that this can be simplified using monads.
i've tried to read it imaging myself as fresh reader and was stopped
at some middle because code was too complicated to understand and
it was completely imobvious (for fresh reader) that we just wrote
innards of monad and then will reduce all this ugly code just to
= calls


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] A free monad theorem?

2006-09-01 Thread Bulat Ziganshin
Hello Benjamin,

Thursday, August 31, 2006, 9:23:55 PM, you wrote:

 The background for my question is an argument I had some time ago with
 someone about what the 'real nature' of monads is. He argued that monads
 are mainly about 'chaining' (somehow wrapped up) values in an associative
 way, refering to the monad laws.

my understanding of monads is that monad is a way to combine
functions. 'bind' operator defines algorithm of this combining for
each concrete monad. some monads thread values, some spread them, some
just sequence computations


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] state and exception or types again...

2006-09-01 Thread Andrea Rossato
Il Fri, Sep 01, 2006 at 10:43:14AM +0400, Bulat Ziganshin ebbe a scrivere:
  The tutorial will have this outline: first we build a monad adding
  output, exception, and state. Then we use monad transformer to take
  out state and output and add debug, doing lifting, put(ing) and
  get(ing) by hand, to understand the central role of type
  matching/construction.
 
 imho, your tutorial makes the error that is a very typical: when you
 write your tutorial you already know what are monads and what the
 program you will construct at the end. but your reader don't know all these!

Neither did I, actually.

 for such fresh reader this looks as you made some strange steps, write
 some ugly code and he don't have chances to understand that this ugly
 code is written just to show that this can be simplified using monads.
 i've tried to read it imaging myself as fresh reader and was stopped
 at some middle because code was too complicated to understand and
 it was completely imobvious (for fresh reader) that we just wrote
 innards of monad and then will reduce all this ugly code just to
 = calls

I do not entirely understand your point. I wrote just the first part
of the tutorial, till the Errare Monadicum Est chapter. From then
on, before writing the tutorial, I needed to understand what I was
headed to and so I wrote the code. Now the task is to explain each
step of that code.

Indeed I'm a fresh reader that did not find anything that she could
find useful to understand monads, and wrote her own.

That is to say, this is the way I came to understand monads. I do not
pretend to teach what monads are, but I hope that, by following the
same path I followed, someone else can get to the point where I am
now.

Where now I am is just another kind of problem. Probably nowhere.

That's it.

Anyway, thanks a lot for your suggestions. I'll try to understand them
and put them in practice.
As far as I can.

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


Re: [Haskell-cafe] Re: data structures question

2006-09-01 Thread Tamas K Papp
On Thu, Aug 31, 2006 at 11:09:07AM +0400, Bulat Ziganshin wrote:
 Hello Benjamin,
 
 Wednesday, August 30, 2006, 11:40:09 PM, you wrote:
 
  Matthias Fischmann wrote:
  The trick is that Int is not the only index data type, but tuples of
  index data types are, too.  Do this:
  
  | type Point = (State, State, Int)
  | type TypeV = Array State Double
  | 
  | matrix :: TypeV
  | matrix = array bounds values
  |where
  |...
 
  Surely you meant to say
 
  | type TypeV = Array Point Double
 
 which will require 128 gigs of memory for 32-bit cpus and even
 slightly more for 64-bit ones :)

Bulat,

Can you please explain this?  The following code works fine for me,
and I don't have that much RAM ;-) It seems I am not getting
something.


import Data.Array

data State = Low | High deriving (Eq,Ord,Ix,Show)

other :: State - State
other High = Low
other Low = High

type Point = (State,State,Int)
type TypeV = Array Point Double

f (Low,Low,a) = a

matrix = array ((Low,Low,0),(Low,Low,4)) [(i,f(i)) | i - range 
((Low,Low,0),(Low,Low,4))]


Thank you,

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


Re: [Haskell-cafe] Re: A free monad theorem?

2006-09-01 Thread Brian Hulley

Benjamin Franksen wrote:

Tomasz Zielonka wrote:

whatever you do, you won't be able to extract an 'a' typed
value, non-bottom from this computation. Cont is defined as:

newtype Cont r a = Cont {runCont :: (a - r) - r)}


So getting the value out of the monad is not a pure function (extract
:: Monad m = m a - a). I think I stated that, already, in my
previous post. I'd even say that the monadic values alone can be
completely meaningless. They often have a meaning only relative to
some environment, thus are (usually) _effectful_ computations. But we
already knew that, didn't we?

The real question (the one that bugs me, anyway) is if one can give a
precise meaning to the informal argument that if the definition of
bind is to be non-trivial then its second argument must be applied to
some non-trivial value at one point (but not, of course, in all
cases, nor necessarily only once), and that this implies that the
computation represented by the first argument must somehow be 'run'
(in some environment) in order to produce such a value.


I think the continuation monad might help to refine the intuition:

   Cont a_r_r = a_C_b_r_r = Cont $ \ b_r -
 a_r_r (\a - runCont (a_C_b_r_r   a)   b_r)

so it is clear that

1) The first computation (a_r_r  x) might involve running the second 
(applying b_r_r to b_r) so it gives a counterexample to the idea that the 
first computation is run to completion before the second one starts, though 
it preserves the intuition that at least the first computation is started 
first.


2) The bind operation has arranged that value(s) of type (a) are supplied in 
the course of running the first computation to the second (in the 
non-trivial case where the second computation is actually run)


Perhaps the argument could be that because the (a) is polymorphic, this 
implies that if the second computation is run at all, at least we know that 
the first computation has already started, and that the (a) came from the 
part of the first computation we've done so far, though of course this is 
still unfortunately very vague.


Regards, Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com 


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


Re: [Haskell-cafe] Re: A free monad theorem?

2006-09-01 Thread Tomasz Zielonka
On Fri, Sep 01, 2006 at 07:22:02AM +0200, Tomasz Zielonka wrote:
  The real question (the one that bugs me, anyway) is if one can give a
  precise meaning to the informal argument that if the definition of bind is
  to be non-trivial then its second argument must be applied to some
  non-trivial value at one point (but not, of course, in all cases, nor
  necessarily only once)
 
 How about using monad laws, specifically:
 
 (return x) = f == f x
 
 We assume that = never uses it's second argument, so:
 
 (return x) = f == (return x) = g
 
 Combining it with the above monad law we get:
 
 f x == (return x) = f == (return x) = g == g x
 
 so
 
 f x = g x
 
 for arbitrary f and g. Let's substitute return for f and
 undefined for g:
 
 return x = undefined x
 
 so
 
 return x = undefined
 
 Now that seems like a very trivial (and dysfunctional) monad.

I just realized that I haven't addressed your exact problem, but maybe
you'll be able to use a similar reasoning to prove your theorem.

What (I think) I proved is that: if = never uses its second argument,
then the monad is dysfunctional (maybe not even a monad at all). Again,
informally, it is obvious.

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


[Haskell-cafe] Rewriting a Python application to Haskell

2006-09-01 Thread basvandijk
Hello,

The company I work for [1] develops highly sensitive trace gas detectors. We 
also develop software that is used to control these detectors from a PC or 
laptop. With this software a user can setup an experiment, execute it and 
analyse and visualise the data in real-time. While executing, the application 
gives commands to the detector and gets concentrations from the detector which 
it plots. See [5] for a screenshot.

The application is written in Python and uses wxPython for its GUI. The 
software is highly threaded; The experiment executor, the analyzer, the 
communication system and the GUI all have their own threads. In order to 
synchronise these threads we make extensive use of locks [2]. This thread 
synchronisation mechanism worked fine in the beginning. However, as the 
application becomes more complex, it is increasingly difficult not to introduce 
bugs that are caused by forgetting to release or acquire locks. Also the use of 
locks makes the code hard to understand. Finally it's hard to compose functions 
that use locks.

I've long been interested in Haskell and played around with it for some time. 
Recently I became aware of the Haskell STM implementation [3]. I think STM can 
solve my thread synchronisation problems. Because of this and because I would 
like to know how suitable Haskell is for developing real-world GUI 
applications, I would like to rewrite our application in Haskell (in my free 
time of course ;-) ). I think I need to use wxHaskell for the GUI because it's 
runs on a lot of platforms and we are currently using wxPython which should 
make the transition easier.

1) I would like to know if its difficult to use wxHaskell and STM side by side 
and if there are any issues I need to know about.

2) Also, we use pySerial [4] for serial communication with the detector. Is 
there something like that for Haskell or is it easy to make it yourself?

3) How portable is Haskell? We like to run our application on Mac, Windows and 
Linux.

Greetings,

Bas van Dijk

[1] http://www.sensor-sense.nl
[2] http://docs.python.org/lib/lock-objects.html
[3] 
http://haskell.org/ghc/docs/latest/html/libraries/stm/Control-Concurrent-STM.html
[4] http://pyserial.sourceforge.net
[5] http://members.home.nl/basvandijk/vc-screenshot.png
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Rewriting a Python application to Haskell

2006-09-01 Thread Neil Mitchell

Hi


1) I would like to know if its difficult to use wxHaskell and STM side by side 
and if there are any issues I need to know about.


I have no idea about wxHaskell and STM, but I found out that hard way
that Gtk2Hs + threads = bad idea. Depending on the machine I used, I
got a wide class of unrepeatable behaviour, and (really) poor
performance. You might find wxHaskell doesn't suffer from these
problems, but I don't know.


3) How portable is Haskell? We like to run our application on Mac, Windows and 
Linux.

The Haskell compiler (GHC) is very portable, and runs on Mac/Windows
and most common Linux architectures. wxHaskell does those 3 platforms
as well. Haskell tends to be very portable. Some of the more advanced
features on some of the less common platforms are sometimes a bit
buggy or untested - but usually there are people who are willing to
work and fix any issues you run into.

Thanks, and good luck

Neil
___
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] Exercise in point free-style

2006-09-01 Thread Neil Mitchell

Hi Julien,


func3 f l = l ++ map f l

func3 f = ap (++) (map f)
func3 = ap (++) . map


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?

I have no idea how to do this - the solution is to log into #haskell
irc and fire off @pl - which automatically converts things to point
free form. I'm not sure if its possible to do without the auxiliary ap
(which is defined in Monad).

Thanks

Neil
___
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 Neil Mitchell

Hi


func2 f g l = filter f (map g l)
is
func2p f g = (filter f) . (map g)


func2 = (. map) . (.) . filter

Again, how anyone can come up with a solution like this, is entirely
beyond me...

Thanks

Neil
___
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 Robert Dockins
On Friday 01 September 2006 11:44, Neil Mitchell wrote:
 Hi

  func2 f g l = filter f (map g l)
  is
  func2p f g = (filter f) . (map g)

 func2 = (. map) . (.) . filter

 Again, how anyone can come up with a solution like this, is entirely
 beyond me...

To answer part of the OP's question, it's always possible to rewrite a lambda 
term using point-free style (using a surprisingly small set of basic 
combinators).  The price you pay is that the new term is often quite a bit 
larger than the old term.  Rewriting complicated lambda terms as point-free 
terms is often of, em, dubious value.  OTOH, it can be interesting for 
understanding arrows, which are a lot like monads in points-free style (from 
what little experience I have with them).

BTW, the process of rewriting can be entirely automated.  I assume the 
lambdabot is using one of the well-known algorithms, probably tweaked a bit.

Goolge combinatory logic or Turner's combinators if you're curious.


 Thanks

 Neil


-- 
Rob Dockins

Talk softly and drive a Sherman tank.
Laugh hard, it's a long way to the bank.
   -- TMBG
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Are associated types synonyms like type classes?

2006-09-01 Thread Brian Smith
I read the easy parts of the Associated Types with Class and Associated Type Synonyms papers. An associated type synonym seems to kind of work similarly to a restricted form of class. In what way are the two following examples different?
 -- define a class with a type synonym, and a set of operations class A a where type B b foo :: a - B b instance A Int where type B = Bool foo = (==0)
 -- define two classes, and an function that . class A a, B b where foo :: a - b instance A Int, B Bool where foo = (==0)Also, has anybody written a paper on the differences between typeclasses + associated types and ML's module system + overloading?
Thanks,Brian
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] Re: data structures question

2006-09-01 Thread Bulat Ziganshin
Hello Tamas,

Friday, September 1, 2006, 1:52:03 PM, you wrote:

  | type Point = (State, State, Int)
  | type TypeV = Array Point Double
 
 which will require 128 gigs of memory for 32-bit cpus and even
 slightly more for 64-bit ones :)

 Bulat,

 Can you please explain this?  The following code works fine for me,
 and I don't have that much RAM ;-) It seems I am not getting
 something.

sorry, it was entirely my mindbug - i imagined that such type means
that array should contain elements for every possible combination of
State+State+Int :)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


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

2006-09-01 Thread John Hughes

From: Julien Oster [EMAIL PROTECTED]
Subject: [Haskell-cafe] Exercise in point free-style

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


Oh, YES!!

Two ways to remove l:

func3a f = uncurry ((.map f).(++)) . pair
func3b f = uncurry (flip (++).map f) . pair

And just to make sure they're right:

propab new f l =
 func3 f l == new f l
 where types = f :: Int-Int

quickCheck (propab func3a)
quickCheck (propab func3b)

If you don't mind swapping the arguments, then

propc f l =
 func3 f l == func3c l f
 where types = f :: Int-Int

func3c l = (l++) . (`map` l)

With the arguments swapped, you can even remove both!

propd f l =
 func3 f l == func3d l f
 where types = f :: Int - Int

func3d = uncurry ((.(flip map)) . (.) . (++)) . pair

MUCH clearer!

The trick is to observe that l is duplicated, so you need to use a 
combinator that duplicates something. The only one available here is pair, 
which you then have to combine with uncurry.


It would be nicer to have

(f  g) x = (f x,g x)

available. ( is one of the arrow combinators). Then you could remove l by

func3e f = uncurry (++) . (id  map f)

which is sort of readable, and remove both by

func3f = (uncurry (++).) . (id ) . map

John 




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


Re: [Haskell-cafe] Are associated types synonyms like type classes?

2006-09-01 Thread Stefan Holdermans

Brian,

I read the easy parts of the Associated Types with Class and  
Associated Type Synonyms papers. An associated type synonym seems  
to kind of work similarly to a restricted form of class. In what  
way are the two following examples different?


-- define a class with a type synonym, and a set of operations
class A a where
type B b
foo :: a - B b

instance A Int where
type B = Bool
foo = (==0)

-- define two classes, and an function that .
class A a, B b where
foo :: a - b

 instance A Int, B Bool where
  foo = (==0)


It is more like -- using multi-parameter type classed with functional  
dependencies (as found, for example, in GHC):


  class A a b | a - b where
foo :: a - b

  instance A Int Bool where
foo = (== 0)

Cheers,

  Stefan
___
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 Udo Stenzel
Julien Oster wrote:
 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?

Sure it is:

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


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.


Udo.
-- 
I'm not prejudiced, I hate everyone equally.


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


Re: [Haskell-cafe] Are associated types synonyms like type classes?

2006-09-01 Thread Bulat Ziganshin
Hello Brian,

Friday, September 1, 2006, 8:32:55 PM, you wrote:

 I read the easy parts of the Associated Types with Class and
 Associated Type Synonyms papers. An associated type synonym seems
 to kind of work similarly to a restricted form of class. In what way
 are the two following examples different? 

     -- define a class with a type synonym, and a set of operations
     class A a where
     type B b
     foo :: a - B b

     instance A Int where
     type B = Bool
     foo = (==0) 

     -- define two classes, and an function that .
     class A a, B b where
     foo :: a - b

  instance A Int, B Bool where
   foo = (==0)

where you've find such unusual syntax? :)  GHC/Hugs supports
multi-parameter type classes (MPTC):

class AB a b where
foo :: a - b

instance AB Int Bool where
    foo = (==0)

AT replaces MPTC with FD (functional dependency), which allows to
specify which type parameter of MPTC is detremined by another one, i.e.:

class AB a b | a-b where 

for further details about MPTC+FD see chapter 7.1.1 in the
http://cvs.haskell.org/Hugs/pages/hugsman/exts.html
 


 Also, has anybody written a paper on the differences between
 typeclasses + associated types and ML's module system + overloading? 

ML Modules and Haskell Type Classes: A Constructive Comparison
http://www.informatik.uni-freiburg.de/~wehr/diplom/Wehr_ML_modules_and_Haskell_type_classes.pdf


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


[Haskell-cafe] getContents and lazy evaluation

2006-09-01 Thread Tamas K Papp
Hi,

I am newbie, reading the Gentle Introduction.  Chapter 7
(Input/Output) says

  Pragmatically, it may seem that getContents must immediately read an
  entire file or channel, resulting in poor space and time performance
  under certain conditions. However, this is not the case. The key
  point is that getContents returns a lazy (i.e. non-strict) list of
  characters (recall that strings are just lists of characters in
  Haskell), whose elements are read by demand just like any other
  list. An implementation can be expected to implement this
  demand-driven behavior by reading one character at a time from the
  file as they are required by the computation.

So what happens if I do

contents - getContents handle
putStr (take 5 contents) -- assume that the implementation 
 -- only reads a few chars
-- delete the file in some way
putStr (take 500 contents) -- but the file is not there now

If an IO function is lazy, doesn't that break sequentiality?  Sorry if
the question is stupid.

Thanks,

Tamas
___
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 Robert Dockins
On Friday 01 September 2006 15:19, Tamas K Papp wrote:
 Hi,

 I am newbie, reading the Gentle Introduction.  Chapter 7
 (Input/Output) says

   Pragmatically, it may seem that getContents must immediately read an
   entire file or channel, resulting in poor space and time performance
   under certain conditions. However, this is not the case. The key
   point is that getContents returns a lazy (i.e. non-strict) list of
   characters (recall that strings are just lists of characters in
   Haskell), whose elements are read by demand just like any other
   list. An implementation can be expected to implement this
   demand-driven behavior by reading one character at a time from the
   file as they are required by the computation.

 So what happens if I do

 contents - getContents handle
 putStr (take 5 contents) -- assume that the implementation
-- only reads a few chars
 -- delete the file in some way
 putStr (take 500 contents) -- but the file is not there now

 If an IO function is lazy, doesn't that break sequentiality?  Sorry if
 the question is stupid.

This is not a stupid question at all, and it highlights the main problem with 
lazy IO.  The solution is, in essence don't do that, because Bad Things will 
happen.  It's pretty unsatisfactory, but there it is.  For this reason, lazy 
IO is widely regarded as somewhat dangerous (or even as an outright 
misfeature, by a few).

If you are going to be doing simple pipe-style IO (ie, read some data 
sequentially, manipulate it, spit out the output),  lazy IO is very 
convenient, and it makes putting together quick scripts very easy.  However, 
if you're doing something more advanced, you'd probably do best to stay away 
from lazy IO.

Welcome to Haskell, BTW  :-)

 Thanks,

 Tamas

-- 
Rob Dockins

Talk softly and drive a Sherman tank.
Laugh hard, it's a long way to the bank.
   -- TMBG
___
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 Duncan Coutts
On Fri, 2006-09-01 at 16:28 -0400, Robert Dockins wrote:
 On Friday 01 September 2006 15:19, Tamas K Papp wrote:
  Hi,
 
  I am newbie, reading the Gentle Introduction.  Chapter 7
  (Input/Output) says
 
Pragmatically, it may seem that getContents must immediately read an
entire file or channel, resulting in poor space and time performance
under certain conditions. However, this is not the case. The key
point is that getContents returns a lazy (i.e. non-strict) list of
characters (recall that strings are just lists of characters in
Haskell), whose elements are read by demand just like any other
list. An implementation can be expected to implement this
demand-driven behavior by reading one character at a time from the
file as they are required by the computation.
 
  So what happens if I do
 
  contents - getContents handle
  putStr (take 5 contents) -- assume that the implementation
   -- only reads a few chars
  -- delete the file in some way
  putStr (take 500 contents) -- but the file is not there now
 
  If an IO function is lazy, doesn't that break sequentiality?  Sorry if
  the question is stupid.
 
 This is not a stupid question at all, and it highlights the main problem with 
 lazy IO.  The solution is, in essence don't do that, because Bad Things will 
 happen.  It's pretty unsatisfactory, but there it is.  For this reason, lazy 
 IO is widely regarded as somewhat dangerous (or even as an outright 
 misfeature, by a few).
 
 If you are going to be doing simple pipe-style IO (ie, read some data 
 sequentially, manipulate it, spit out the output),  lazy IO is very 
 convenient, and it makes putting together quick scripts very easy.  However, 
 if you're doing something more advanced, you'd probably do best to stay away 
 from lazy IO.

Since working on Data.ByteString.Lazy I'm now even more of a pro-lazy-IO
zealot than I was before ;-)

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. The
same can be done with lazy I, though it requires using imprecise
exceptions which some people grumble about. So I would contend that lazy
IO is actually applicable in rather a wider range of circumstances than
you might. :-)

Note also, that with lazy IO we can write really short programs that are
blindingly quick. Lazy IO allows us to save a copy through the Handle
buffer.

BTW in the above case the bad thing that will happen is that contents
will be truncated. As I said, I think it's better to throw an exception,
which is what Data.ByteString.Lazy.hGetContents does.

Duncan

___
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 Robert Dockins
On Friday 01 September 2006 16:46, Duncan Coutts wrote:
 On Fri, 2006-09-01 at 16:28 -0400, Robert Dockins wrote:
  On Friday 01 September 2006 15:19, Tamas K Papp wrote:
   Hi,
  
   I am newbie, reading the Gentle Introduction.  Chapter 7
   (Input/Output) says
  
 Pragmatically, it may seem that getContents must immediately read an
 entire file or channel, resulting in poor space and time performance
 under certain conditions. However, this is not the case. The key
 point is that getContents returns a lazy (i.e. non-strict) list of
 characters (recall that strings are just lists of characters in
 Haskell), whose elements are read by demand just like any other
 list. An implementation can be expected to implement this
 demand-driven behavior by reading one character at a time from the
 file as they are required by the computation.
  
   So what happens if I do
  
   contents - getContents handle
   putStr (take 5 contents) -- assume that the implementation
  -- only reads a few chars
   -- delete the file in some way
   putStr (take 500 contents) -- but the file is not there now
  
   If an IO function is lazy, doesn't that break sequentiality?  Sorry if
   the question is stupid.
 
  This is not a stupid question at all, and it highlights the main problem
  with lazy IO.  The solution is, in essence don't do that, because Bad
  Things will happen.  It's pretty unsatisfactory, but there it is.  For
  this reason, lazy IO is widely regarded as somewhat dangerous (or even as
  an outright misfeature, by a few).
 
  If you are going to be doing simple pipe-style IO (ie, read some data
  sequentially, manipulate it, spit out the output),  lazy IO is very
  convenient, and it makes putting together quick scripts very easy. 
  However, if you're doing something more advanced, you'd probably do best
  to stay away from lazy IO.

 Since working on Data.ByteString.Lazy I'm now even more of a pro-lazy-IO
 zealot than I was before ;-)

 In practise I expect that most programs that deal with file IO strictly
 do not handle the file disappearing under them very well either.

That's probably true, except for especially robust applications where such a 
thing is a regular (or at least expected) event.

 At best 
 the probably throw an exception and let something else clean up. The
 same can be done with lazy I, though it requires using imprecise
 exceptions which some people grumble about. So I would contend that lazy
 IO is actually applicable in rather a wider range of circumstances than
 you might. :-)

Perhaps I should be more clear.  When I said advanced above I meant any use 
whereby you treat a file as random access, read/write storage, or do any kind 
of directory manipulation (including deleting and or renaming files).  Lazy 
I/O (as it currently stands) doesn't play very nice with those use cases.

I agree generally with the idea that lazy I/O is good.  The problem is that it 
is a leaky abstraction; details are exposed to the user that should ideally 
be completely hidden.  Unfortunately, the leaks aren't likely to get plugged 
without pretty tight operating system support, which I suspect won't be 
happening anytime soon.

 Note also, that with lazy IO we can write really short programs that are
 blindingly quick. Lazy IO allows us to save a copy through the Handle
 buffer.

 BTW in the above case the bad thing that will happen is that contents
 will be truncated. As I said, I think it's better to throw an exception,
 which is what Data.ByteString.Lazy.hGetContents does.

Well, AFAIK, the behavior is officially undefined, which is my real beef.  I 
agree that it _should_ throw an exception.

 Duncan

-- 
Rob Dockins

Talk softly and drive a Sherman tank.
Laugh hard, it's a long way to the bank.
   -- TMBG
___
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 Donn Cave
On Fri, 1 Sep 2006, Robert Dockins wrote:
 On Friday 01 September 2006 16:46, Duncan Coutts wrote:
...
 Note also, that with lazy IO we can write really short programs that are
 blindingly quick. Lazy IO allows us to save a copy through the Handle
 buffer.

(Never understood why some people think it would be such a good thing
to be blinded, but as long as it's you and not me ... )


 BTW in the above case the bad thing that will happen is that contents
 will be truncated. As I said, I think it's better to throw an exception,
 which is what Data.ByteString.Lazy.hGetContents does.
 
 Well, AFAIK, the behavior is officially undefined, which is my real beef.  I 
 agree that it _should_ throw an exception.

Is this about Microsoft Windows?  On UNIX, I would expect deletion of
a file to have no effect on I/O of any kind on that file.  I thought
the problems with hGetContents more commonly involve operations on
the file handle, e.g., hClose.

Donn Cave, [EMAIL PROTECTED]

___
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 Robert Dockins
On Friday 01 September 2006 18:01, Donn Cave wrote:
 On Fri, 1 Sep 2006, Robert Dockins wrote:
  On Friday 01 September 2006 16:46, Duncan Coutts wrote:

 ...

  Note also, that with lazy IO we can write really short programs that are
  blindingly quick. Lazy IO allows us to save a copy through the Handle
  buffer.

 (Never understood why some people think it would be such a good thing
 to be blinded, but as long as it's you and not me ... )

  BTW in the above case the bad thing that will happen is that contents
  will be truncated. As I said, I think it's better to throw an exception,
  which is what Data.ByteString.Lazy.hGetContents does.
 
  Well, AFAIK, the behavior is officially undefined, which is my real beef.
   I agree that it _should_ throw an exception.

 Is this about Microsoft Windows?  On UNIX, I would expect deletion of
 a file to have no effect on I/O of any kind on that file.  I thought
 the problems with hGetContents more commonly involve operations on
 the file handle, e.g., hClose.

Ahh... I think you're right.

However, this just illustrates the problem.  The point is that the answer the 
question what happens when I do odd thing involving lazy I/O is it 
depends.  And to the obvious followup question what does it depend on? the 
answer is well it's complicated.

   Donn Cave, [EMAIL PROTECTED]

-- 
Rob Dockins

Talk softly and drive a Sherman tank.
Laugh hard, it's a long way to the bank.
   -- TMBG
___
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 Duncan Coutts
On Fri, 2006-09-01 at 17:36 -0400, Robert Dockins wrote:

 Perhaps I should be more clear.  When I said advanced above I meant any 
 use 
 whereby you treat a file as random access, read/write storage, or do any kind 
 of directory manipulation (including deleting and or renaming files).  Lazy 
 I/O (as it currently stands) doesn't play very nice with those use cases.

Indeed, it can't be used in that case.

 I agree generally with the idea that lazy I/O is good.  The problem is that 
 it 
 is a leaky abstraction; details are exposed to the user that should ideally 
 be completely hidden.  Unfortunately, the leaks aren't likely to get plugged 
 without pretty tight operating system support, which I suspect won't be 
 happening anytime soon.

Yes it is leaky.

 Well, AFAIK, the behavior is officially undefined, which is my real beef.  I 
 agree that it _should_ throw an exception.

Ah, I had thought it was defined to simply truncate. It being undefined
isn't good. It seems that it would be straightforward to define it to
have the truncation behaviour. If Haskell-prime gets imprecise
exceptions then that could be changed.

Duncan

___
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] Re: Exercise in point free-style

2006-09-01 Thread Thomas Davie

Shorter, although perhaps less insightful.

Bob

On 2 Sep 2006, at 01:36, Lennart Augustsson wrote:

An easy way to solve this is to ask lambdabot.  Log on to the  
Haskell IRC channel:

lennart: @pl  \ f l - l ++ map f l
lambdabot: ap (++) . map

Notice how it's much shorter than the Hughes' solution. :)

-- Lennart

On Sep 1, 2006, at 13:11 , John Hughes wrote:


From: Julien Oster [EMAIL PROTECTED]
Subject: [Haskell-cafe] Exercise in point free-style

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


Oh, YES!!

Two ways to remove l:

func3a f = uncurry ((.map f).(++)) . pair
func3b f = uncurry (flip (++).map f) . pair

And just to make sure they're right:

propab new f l =
 func3 f l == new f l
 where types = f :: Int-Int

quickCheck (propab func3a)
quickCheck (propab func3b)

If you don't mind swapping the arguments, then

propc f l =
 func3 f l == func3c l f
 where types = f :: Int-Int

func3c l = (l++) . (`map` l)

With the arguments swapped, you can even remove both!

propd f l =
 func3 f l == func3d l f
 where types = f :: Int - Int

func3d = uncurry ((.(flip map)) . (.) . (++)) . pair

MUCH clearer!

The trick is to observe that l is duplicated, so you need to use a  
combinator that duplicates something. The only one available here  
is pair, which you then have to combine with uncurry.


It would be nicer to have

(f  g) x = (f x,g x)

available. ( is one of the arrow combinators). Then you could  
remove l by


func3e f = uncurry (++) . (id  map f)

which is sort of readable, and remove both by

func3f = (uncurry (++).) . (id ) . map

John


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


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


___
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


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

2006-09-01 Thread Donald Bruce Stewart
haskell:
 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?

The solution is to install lambdabot ;)

Point free refactoring:
lambdabot pl func3 f l = l ++ map f l
func3 = ap (++) . map

Find the type:
lambdabot type ap (++) . map
forall b. (b - b) - [b] - [b]

Get some free theorems:
lambdabot free f :: (b - b) - [b] - [b]
f . g = h . f = map f . f g = f h . map f

:)

-- Don
___
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 Donald Bruce Stewart
haskell:
 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?

Similarly:

lambdabot pl func2 f g l = filter f (map g l)
func2 = (. map) . (.) . filter

:)
___
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 Donn Cave
Quoth Julien Oster [EMAIL PROTECTED]:
...
| 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.

That's actually a much more general problem, one that I imagine applies
to hPutStr et al. too.  Application level writes are ordinarily buffered
in process space by the I/O library, so output from an ordinary C program
may not appear on disk (or in kernel space disk I/O buffer) until just
before the program exits.

| 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?

Quite a few reasons, depending on how you define communication.  You
might even be tempted to use hGetContents in such cases.  For example,
one common way to share a file is to interlock around some resource,
and when you acquire the lock, you read the file (get its contents)
and release the lock.

Donn Cave, [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe