Re: [Haskell-cafe] Re: Referential Transparency and Monads

2009-04-09 Thread Jonathan Cast
On Fri, 2009-04-10 at 01:03 -0400, Brandon S. Allbery KF8NH wrote:
> On 2009 Apr 10, at 0:52, Jonathan Cast wrote:
> > On Fri, 2009-04-10 at 00:46 -0400, Brandon S. Allbery KF8NH wrote:
> >>> IO a  ~  World -> (a, World)
> >>
> >> I still don't understand this; we are passing a World and getting a
> >> World back,
> >
> > We are?  Why do you think that?
> 
> Because that's what (World -> (a,World)) means, last I checked.

Does

undefined :: (a, World)

contain a World?

jcc


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


Re: [Haskell-cafe] Referential Transparency and Monads

2009-04-09 Thread Jonathan Cast
On Fri, 2009-04-10 at 07:29 +0400, Miguel Mitrofanov wrote:
> On 10 Apr 2009, at 06:30, Jonathan Cast wrote:
> >  do
> > s <- readFile "/my_file"
> > writeFile "/my_file" "Hello, world!\n"
> > threadDelay 1 -- If you don't like threadDelay, just  
> > substitute forcing
> >   -- an expensive thunk here
> > writeFile "/my_file" s
> >
> > As a function from initial state to final state, this program is just
> > the identity;
> 
> No, since world state includes the user state itself, not just files  
> contents.

My programs are passing me around inside a state token?

jcc


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


Re: [Haskell-cafe] Re: Referential Transparency and Monads

2009-04-09 Thread Jonathan Cast
On Fri, 2009-04-10 at 00:46 -0400, Brandon S. Allbery KF8NH wrote:
> On 2009 Apr 10, at 0:33, Heinrich Apfelmus wrote:
> > Luke Palmer wrote:
> >> Miguel Mitrofanov wrote:
> >>
> >>> I'm not sure what you mean by that, but semantically IO is  
> >>> definitely
>  *not* a state monad.  Under any circumstances or any set of  
>  assumptions.
> 
> >>> Ehm? Why not?
> >>
> >> Mainly forkIO.  There may be other reasons.
> >  loop' :: IO ()
> >  loop' = putStr "o" >> loop'
> >
> > are indistinguishable in the
> >
> >  IO a  ~  World -> (a, World)
> 
> 
> I still don't understand this; we are passing a World and getting a  
> World back,

We are?  Why do you think that?

jcc


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


Re: [Haskell-cafe] Referential Transparency and Monads

2009-04-09 Thread Jonathan Cast
On Thu, 2009-04-09 at 22:47 -0400, Brandon S. Allbery KF8NH wrote:
> On 2009 Apr 9, at 22:30, Jonathan Cast wrote:
> > On Thu, 2009-04-09 at 21:57 -0400, Brandon S. Allbery KF8NH wrote:
> >> On 2009 Apr 9, at 16:09, Luke Palmer wrote:
> >>> On Thu, Apr 9, 2009 at 1:33 PM, Miguel Mitrofanov
> >>>  wrote:
> >>>I'm not sure what you mean by that, but semantically
> >>>IO is definitely
> >>>*not* a state monad.  Under any circumstances or any
> >>>set of assumptions.
> >>>
> >>>Ehm? Why not?
> >>>
> >>> Mainly forkIO.  There may be other reasons.
> >>
> >> I thought I had excluded that stuff to simplify the question; the  
> >> fact
> >> that IO is Haskell's toxic waste dump is more or less irrelevant to
> >> the core concept.
> >
> > Well, the `core concept' of IO includes the concept of a user who's
> > watching and interacting with your program as it runs, no?
> 
> Yes.  That's the opaque "real world";  an I/O operation conceptually  
> modifies this state,

Pedantic nit-pick: modification is not referentially transparent.  You
mean `returns a modified copy'.

> which is how things get tied together.  Ordinary  
> user programs can't interact with the "real world" sate except via  
> functions defined on IO, which are assumed to modify the state; that's  
> exactly how non-RT actions are modeled via RT code.
> 
> Stuff like forkIO and newIORef can also be understood that way, it's  
> just a bit more complex to follow them around.
> 
> Please note that ghc *does* implement IO (from Core up, at least) this  
> way, modulo unboxed tuples, so claims that it is "wrong" are dubious  
> at best.

No, GHC implements IO using an internal side-effectful language.  (Note
that the `state' IO uses internally is an (un-boxed and un-pointed)
0-bit word!  It certainly doesn't have enough semantic content
to /actually/ contain the entire state of the computer.)  The difference
between GHC core and a truly referentially transparent language is that
you can't implement unsafePerformIO unless your language has side
effects.

Oh, and I should have cited Tackling the Awkward Squad as the source of
my dubious claim.

> > s <- readFile "/my_file"
> > writeFile "/my_file" "Hello, world!\n"
> > threadDelay 1 -- If you don't like threadDelay, just  
> > substitute forcing
> >   -- an expensive thunk here
> > writeFile "/my_file" s
> >
> > As a function from initial state to final state, this program is just
> > the identity; but surely this program should be considered different
> 
> It is?
> 
>  > -- these implicitly are considered to return a modified RealWorld
>  > readFile :: RealWorld -> (String,RealWorld)
>  > writeFile :: RealWorld -> ((),RealWorld)
>  > threadDelay :: RealWorld -> ((),RealWorld)
>  >
>  > main :: RealWorld -> ((),RealWorld)
>  > main state =
>  >   case readFile state "/my_file" of
>  > (s,state') ->
>  >case writeFile state' "/my_file" "Hello, world!\n" of
>  >  (_,state'') ->
>  > case threadDelay state'' 1 of
>  >   (_,state'') -> writeFile "/my_file" s state''

(This has arguments very much in the wrong order throughout, of course.)

> This is just the State monad, unwrapped.

What on earth does that have to do with anything?  If I change your last
line to

> (_,state''') -> case writeFile "/my_file" s state''' of
>(x, state'''') -> (x, state'''')

Then I can observe that state'''', if it really names the current state
of the system as of the program's finish-point, is exactly equivalent to
state (e.g., in both states every file has exactly the same contents).
(The only difference, which I forgot, is that the current time is >
10sec later than in state.  Doesn't affect the point.)

Now, the *definition* you gave is, in form, different than the
definition of

  threadDelay 1

However, the point of referential transparency is that you can inline
the definitions of readFile and writeFile into the scrutinees of your
case statements, and then (possibly after something like a case-of-case
transformation) you can eliminate the case expressions and intermediate
stat

Re: [Haskell-cafe] Referential Transparency and Monads

2009-04-09 Thread Jonathan Cast
On Thu, 2009-04-09 at 21:57 -0400, Brandon S. Allbery KF8NH wrote:
> On 2009 Apr 9, at 16:09, Luke Palmer wrote:
> > On Thu, Apr 9, 2009 at 1:33 PM, Miguel Mitrofanov
> >  wrote:
> > I'm not sure what you mean by that, but semantically
> > IO is definitely
> > *not* a state monad.  Under any circumstances or any
> > set of assumptions.
> > 
> > 
> > Ehm? Why not?
> > 
> > Mainly forkIO.  There may be other reasons.
> > 
> 
> 
> I thought I had excluded that stuff to simplify the question; the fact
> that IO is Haskell's toxic waste dump is more or less irrelevant to
> the core concept.

Well, the `core concept' of IO includes the concept of a user who's
watching and interacting with your program as it runs, no?

Say I know that a file named `/my_file' exists and is readable and
writeable and etc.  Now consider the program

  do
 s <- readFile "/my_file"
 writeFile "/my_file" "Hello, world!\n"
 threadDelay 1 -- If you don't like threadDelay, just substitute forcing
   -- an expensive thunk here
 writeFile "/my_file" s

As a function from initial state to final state, this program is just
the identity; but surely this program should be considered different
than just

  threadDelay 1

.  To give a meaningful semantics to IO, you have to consider the
intermediate state(s) the system goes through, where a state monad
denotation for IO would discard them.

jcc


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


Re: [Haskell-cafe] Referential Transparency and Monads

2009-04-09 Thread Jonathan Cast
On Thu, 2009-04-09 at 12:31 -0400, Brandon S. Allbery KF8NH wrote:
> On 2009 Apr 9, at 11:47, Mark Spezzano wrote:
> > How exactly do monads “solve” the problem of referential
> > transparency? I understand RT to be such that a function can be
> > replaced with a actual value.
> >  
> > Since a monad could potentially encapsulate any other value—say,
> > data read from a keyboard—doesn’t that violate the assumption of RT
> > on monads?

> Monads provide a way to carry extra data or operations around with
> their values.  IO passes an opaque "world state" around in the
> background, conceptually I/O operations modify the "world state" and
> it is in fact always valid to replace the monadified version with the
> unwrapped version --- ignoring IORefs, IO is just a simple state
> monad.

I'm not sure what you mean by that, but semantically IO is definitely
*not* a state monad.  Under any circumstances or any set of assumptions.

GHC *implements* IO as a state monad, but not because it semantically
is.  Rather, GHC's back-end language (STG) is an *impure* lazy
functional language, supplying primitive functions with (ultimate)
result type

(# State# s, alpha #)

, for some alpha,[1] that are side-effectful.  The intention is that the
State# s component (which has almost no run-time representation) is used
to ensure a strict sequencing of the evaluation of these expressions ---
which intention can be violated by using the operations unsafePerformIO
and unsafeInterleaveIO --- allowing the language to be both
side-effectful and lazy without the programmer necessarily effectively
losing the ability to control what the outcome of running the program
will be.

But that has nothing to do with referential transparency, because the
language those tricks are used in is not referentially transparent.
It's just an implementation technique for implementing a referentially
transparent source language on a non-referentially transparent
imperative stored-memory computer.

jcc

[1] As pointed out in another thread a couple of weeks ago, the order of
these components is reversed: they should be

(# alpha, State# s #)

It's probably too late to change it now, though.


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


Re: [Haskell-cafe] Re: Re: Monads from Functors

2009-04-08 Thread Jonathan Cast
On Thu, 2009-04-09 at 01:24 +0200, Ben Franksen wrote:
> BTW, is this (ContT t) somehow related to the 'free monad' over t?

The free monad over t is just

  data FreeMonad t a
= Return a
| JoinLift (t (FreeMonad t a))
  instance Functor t => Monad (FreeMonad t) where
return = Return
Return x >>= f = f x
JoinLift a >>= f = JoinLift ((>>= f) <$> a)
  lift :: Functor t => t a -> FreeMonad t a
  lift a = JoinLift (return <$> a)

So they're obviously different.  Here's what free monads are for:
picking a functor f so that FreeMonad f becomes a randomly chosen
monad :), we could define

  data IOStmt a
= GetChar (Char -> a)
| PutChar Char a
  instance Functor IOStmt where
fmap f (GetChar g) = GetChar (f . g)
fmap f (PutChar ch x) = PutChar ch (f x)
  getCharStmt :: IOStmt Char
  getCharStmt = GetChar id
  putCharStmt :: Char -> IOStmt ()
  putCharStmt ch = PutChar ch ()

  type IO = FreeMonad IOStmt
  getChar :: IO Char
  getChar = lift getCharStmt
  putChar :: Char -> IO ()
  putChar = lift . putCharStmt

jcc


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


Re: [Haskell-cafe] A challenge

2009-04-08 Thread Jonathan Cast
On Wed, 2009-04-08 at 17:30 +0200, Thomas Davie wrote:
> On 8 Apr 2009, at 17:20, Jonathan Cast wrote:
> 
> > On Wed, 2009-04-08 at 16:57 +0200, Thomas Davie wrote:
> >> We have two possible definitions of an "iterateM" function:
> >>
> >> iterateM 0 _ _ = return []
> >> iterateM n f i = (i:) <$> (iterateM (n-1) f =<< f i)

> >> iterateM n f i = sequence . scanl (>>=) (return i) $ replicate n f
> >>
> >> The former uses primitive recursion, and I get the feeling it should
> >> be better written without it.  The latter is quadratic time – it
> >> builds up a list of monadic actions, and then runs them each in turn.
> >
> > It's also quadratic in invocations of f, no?  If your monad's (>>=)
> > doesn't object to being left-associated (which is *not* the case for
> > free monads), then I think
> >
> > iterateM n f i = foldl (>>=) (return i) $ replicate n f
> 
> But this isn't the same function – it only gives back the final  
> result, not the intermediaries.

True.  Should have read more carefully.

jcc


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


Re: [Haskell-cafe] A challenge

2009-04-08 Thread Jonathan Cast
On Wed, 2009-04-08 at 16:57 +0200, Thomas Davie wrote:
> We have two possible definitions of an "iterateM" function:
> 
> iterateM 0 _ _ = return []
> iterateM n f i = (i:) <$> (iterateM (n-1) f =<< f i)
> 
> iterateM n f i = sequence . scanl (>>=) (return i) $ replicate n f
> 
> The former uses primitive recursion, and I get the feeling it should  
> be better written without it.  The latter is quadratic time – it  
> builds up a list of monadic actions, and then runs them each in turn.

It's also quadratic in invocations of f, no?  If your monad's (>>=)
doesn't object to being left-associated (which is *not* the case for
free monads), then I think

iterateM n f i = foldl (>>=) (return i) $ replicate n f

would be both correct and linear.  If you're monad's (>>=) is itsef
quadratic in time when left-associated, you can try applying a CPS
transformation to fix the problem.[1]

jcc

[1] http://wwwtcs.inf.tu-dresden.de/~voigt/mpc08.pdf


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


Re: [Haskell-cafe] System.Process.Posix

2009-04-07 Thread Jonathan Cast
On Tue, 2009-04-07 at 14:31 +0100, Neil Mitchell wrote:
> Hi
> 
> >>> Is it me or the above package is not included in Hoogle?
> >>
> >> afair, Neil, being windows user, includes only packages available for
> >> his own system
> >>
> >> there was a large thread a few months ago and many peoples voted for
> >> excluding any OS-specific packages at all since this decreases
> >> portability of code developed by Hoogle users :)))
> >
> > Urm, I realize that was half in jest, but no.  It just makes Hoogle less
> > useful.  If I need to fork, I need to fork, and no amount of
> > sugarcoating is going to get around that.
> 
> I was implementing full package support last weekend. With any luck,
> I'll manage to push the changes tonight. If not, I'll push them as
> soon as I get back from holiday (a week or so)

Yay!

jcc


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


Re: [Haskell-cafe] Missing dependency?

2009-04-02 Thread Jonathan Cast
On Thu, 2009-04-02 at 16:13 -0700, Lyle Kopnicky wrote:
> Hi folks,
> 
> Since the time package is not included in ghc-6.10.2, I installed it
> via cabal. Then I tried to configure my project, and it says that the
> dependency is missing. Mysterious. Can anyone explain?
> 
> l...@lwk-desktop:~/devel/vintage-basic$ ghc-pkg list
> /usr/local/lib/ghc-6.10.2/./package.conf:
> Cabal-1.6.0.3, HUnit-1.2.0.3, QuickCheck-1.2.0.0, array-0.2.0.0,
> base-3.0.3.1, base-4.1.0.0, bytestring-0.9.1.4,
> containers-0.2.0.1,
> directory-1.0.0.3, (dph-base-0.3), (dph-par-0.3),
> (dph-prim-interface-0.3), (dph-prim-par-0.3), (dph-prim-seq-0.3),
> (dph-seq-0.3), editline-0.2.1.0, filepath-1.1.0.2, (ghc-6.10.2),
> ghc-prim-0.1.0.0, haddock-2.4.2, haskell-src-1.0.1.3,
> haskell98-1.0.1.0, hpc-0.5.0.3, html-1.0.1.2, integer-0.1.0.1,
> mtl-1.1.0.2, network-2.2.1, old-locale-1.0.0.1, old-time-1.0.0.2,
> packedstring-0.1.0.1, parallel-1.1.0.1, parsec-2.1.0.1,
> pretty-1.0.1.0, process-1.0.1.1, random-1.0.0.1,
> regex-base-0.72.0.2, regex-compat-0.71.0.1, regex-posix-0.72.0.3,
> rts-1.0, stm-2.1.1.2, syb-0.1.0.1, template-haskell-2.3.0.1,
> unix-2.3.2.0, xhtml-3000.2.0.1
> /home/lwk/.ghc/i386-linux-6.10.2/package.conf:
> HTTP-4000.0.4, time-1.1.2.3, zlib-0.5.0.0
> l...@lwk-desktop:~/devel/vintage-basic$ runhaskell Setup.hs configure
> Configuring vintage-basic-1.0.1...
> Setup.hs: At least the following dependencies are missing:
> time >=1.1
> l...@lwk-desktop:~/devel/vintage-basic$ 

You need to use runhaskell Setup.hs configure --user, or else re-install
time globally (as root).

jcc


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


Re: [Haskell-cafe] Re: Exception handling in numeric computations

2009-03-30 Thread Jonathan Cast
On Sat, 2009-03-28 at 01:27 +0100, Henning Thielemann wrote:
> Jonathan Cast schrieb:
> 
> >> i.e., that application's
> >> file decoding result should be an Either type that anticipates that
> >> the file encoding may be invalid.
> > 
> > This is pretty standard, I thought.  Do people write Haskell file input
> > methods that are undefined (`throw exceptions') on invalid inputs (e.g.,
> > do people use read to parse input from users or the file system[1])?
> 
> With
> 
>   case reads str of
>  [(x, "")] -> Just x
>  _ -> Nothing
> 
> you are safe. (I think it's now available as maybeRead.)

Hmm, hoogle doesn't know that name.

> In general, relying on a well-formed input file is an error. However, if
> your program detects a format error in file input, it could throw an
> exception. But this means that your program must be prepared for these
> problems.

Right.

> >> I will also guess if the file is unreadable because of an external
> >> I/O problem like no read access to file or filesystem, you would
> >> similarly expect this to be treated like that - I mean, ideally, e.g.,
> >> hGetLine :: Handle -> IO (Either IOError String)
> > 
> > IO is an exception monad already.  I don't think there's an objection to
> > throwing exceptions with throwIO and catching them in IO; my objection,
> > at least, is to designing your program to throw exceptions from
> > (ostensibly...) *pure* code and catch those in IO, in a live
> > environment.
> 
> Actually, I really object to have exception handling built into IO
> monad. Especially with extensible-exceptions package you can hide which
> kinds of exceptions can occur in a piece of code, which is a bad thing.
> When it comes to lazy I/O, which is problematic in itself, it is better
> to have explicit exceptions (i.e. IO (Either IOError String)) on top of
> exception-free IO. See the recent thread on safe lazy I/O:
>http://www.haskell.org/pipermail/haskell-cafe/2009-March/058205.html

Yi's new parsing library (just finished the paper a couple days ago)
seems quite appropriate to a lazy IO library; for that library, partial
grammars are errors anyway, so the issue doesn't really arise.

If you want IO failure/parsing failure handling in lazy IO, my
preference would be for a separate failure-handling hook (which can
throw an asynchronous exception if needed) rather than for any kind of
synchronous exception mechanism per se.  There's really not much you can
do, except tell the user either `hey, that doesn't look like valid
input!' or `sorry, the other side of the network connection
disappeared', and hope the operator can correct the issue.  I don't
think it's really important to let the input processing (as opposed to
parsing) code handle the situation specifically.

jcc


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


Re: [Haskell-cafe] Re: Exception handling in numeric computations

2009-03-30 Thread Jonathan Cast
On Fri, 2009-03-27 at 21:16 -0700, Donn Cave wrote:
> Quoth Henning Thielemann ,
> > On Fri, 27 Mar 2009, Donn Cave wrote:
> >
> >> Quoth Jonathan Cast ,
> >>
> >>> An `error' is any condition where the correct response is for the
> >>> programmer to change the source code :)
> >>
> >> That's a broad category, that overlaps with conditions where there
> >> are one or more correct responses for the original program as well.
> >>
> >> If I throw exceptions within the type system, using IO or whatever,
> >> and at some later time observe that I have caught one that would
> >> have been better handled closer to its source, for example.  I've
> >> already technically satisfied my requirement, since everything is
> >> in an exception monad, but the exception is still a bug.
> >
> > I don't understand this one.
> 
> A lame attempt to demonstrate that "condition where [a] correct
> response is to change the code"

Please don't mis-quote me.  I said `the' correct response.  Both
programming and operating computers are goal-directed processes; an
error is a situation where the program detects a bug such that it cannot
make progress toward the current goal without the programmer going and
fixing that bug.

If you have a condition where there is something (useful...) you want to
do within the context of the current source code, do not use an error to
signal that condition.  Use an exception.

> applies to too many cases to be
> useful.  (And that there are no cases where [the only] correct
> response is to change the code.)

I think Henning's response, and others, have adequately covered this.

jcc


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


Re: [Haskell-cafe] Re: Exception handling in numeric computations

2009-03-29 Thread Jonathan Cast
On Sat, 2009-03-28 at 12:51 +0300, Gregory Petrosyan wrote:
> On Sat, Mar 28, 2009 at 10:53 AM, Ketil Malde  wrote:
> > So the difference between an exception or an error type is mainly what
> > you intend to do about it.  There's no point in wrapping divisions in
> > Maybe unless you actually are able to do something useful to recover
> > from a zero denominator.
> 
> That is exactly the point I was trying to make.
> 
> When I write a code, I can't say in advance, in what way it will be used.
> So, for dealing with errors, I have to choose one way or another, mostly
> without that knowledge. When I'm using e.g. C++, it's easy:
> something like mantra "when in doubt, throw an exception" :-)
> combined with RAII, works good (but not ideal, of course).
> 
> So, I'll ask again: when I program in Haskell, what mechanism should I use?

If you don't know, use a (true) exception.  That is, Left or Exception
or throwIO.

Only use error or throw when you *know* the condition is un-recoverable.

jcc


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


Re: [Haskell-cafe] Re: A bit of a shock - Memoizing functions

2009-03-27 Thread Jonathan Cast
On Fri, 2009-03-27 at 14:26 -0700, Kirk Martinez wrote:
> Your powersOfTwo function, since it gets memoized automatically (is
> this the case for all functions of zero arguments?),

It is the case for all functions which have zero arguments *at the time
they are presented to the code generator*.  The infamous evil
monomorphism restriction arises from the fact that overloaded
expressions, such as

negative_one = exp(pi * sqrt(-1))

look like functions of zero arguments, but are not, and hence do not get
memoized.  This behavior was considered sufficiently surprising, when it
was discovered in early Haskell compilers, that the construct was
outlawed from the language entirely.

jcc


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


Re: [Haskell-cafe] Re: Exception handling in numeric computations

2009-03-27 Thread Jonathan Cast
On Fri, 2009-03-27 at 20:38 +0300, Gregory Petrosyan wrote:
> On Fri, Mar 27, 2009 at 7:31 PM, Donn Cave  wrote:
> > Quoth John Lato ,
> >
> >> An exception is caused by some sort of interaction with the run-time
> >> system (frequently a hardware issue).  The programmer typically can't
> >> check for these in advance, but can only attempt to recover after
> >> they've happened.
> >>
> >> An error is some sort of bug that should be fixed by the programmer.
> >
> > I have never felt that I really understood that one.
> 
> Me too :-)
> 
> BTW, John, how often do you encounter _hardware_ issues compared to "errors"?

Can't speak for anyone else, but I usually encounter hardware issues
just before I replace the hardware...

> Is an "out of memory" thing an error or exception?
> You will say "exception, for sure", wouldn't you? :-)

No.  GHC possesses an out-of-memory exception that (IIRC) it never
throws, because it's simply not worth trying to recover from heap
exhaustion.  Maybe 20 years ago it was, but these days a program that
manages to exhaust space is almost certainly either buggy or poorly
optimized.

An `error' is any condition where the correct response is for the
programmer to change the source code :)

> And if it is a
> result of applying
> known-to-be-very-memory-hungry algorithms to non-trivial input? Looks like
> programmer's error, doesn't it?

See above.

> And I think I can provide lots of similar examples.
> 
> If there exists separation between errors and exceptions, it should be
> very strong
> and evident — otherwise "casual programmers" like myself will need to
> stare at the
> ceiling every time they write something to decide what suits best.

Protip: try pacing instead of staring at the ceiling.

jcc


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


Re: [Haskell-cafe] Re: Exception handling in numeric computations

2009-03-27 Thread Jonathan Cast
On Fri, 2009-03-27 at 09:31 -0700, Donn Cave wrote:
> Quoth John Lato ,
> 
> > An exception is caused by some sort of interaction with the run-time
> > system (frequently a hardware issue).  The programmer typically can't
> > check for these in advance, but can only attempt to recover after
> > they've happened.
> >
> > An error is some sort of bug that should be fixed by the programmer.
> 
> I have never felt that I really understood that one.
> 
> What about invalid inputs?  Say someone encounters a disk full error,
> and the resulting partly written file is now unreadable data for its
> intended application because of an invalid file encoding?  Is that
> an exception, or a bug that should be fixed?

NB: Of course it's a bug: if the disk is full, the partially written
file should be discarded and the previous version retained.  I'm not
going to hold you accountable for Unix's bugs, though.

> My guess is that you'll say it's a bug,

I think you mean `exception' here.

> i.e., that application's
> file decoding result should be an Either type that anticipates that
> the file encoding may be invalid.

This is pretty standard, I thought.  Do people write Haskell file input
methods that are undefined (`throw exceptions') on invalid inputs (e.g.,
do people use read to parse input from users or the file system[1])?

> I will also guess if the file is unreadable because of an external
> I/O problem like no read access to file or filesystem, you would
> similarly expect this to be treated like that - I mean, ideally, e.g.,
> hGetLine :: Handle -> IO (Either IOError String)

IO is an exception monad already.  I don't think there's an objection to
throwing exceptions with throwIO and catching them in IO; my objection,
at least, is to designing your program to throw exceptions from
(ostensibly...) *pure* code and catch those in IO, in a live
environment.

> Does that make sense so far?

jcc

[1] This post should not be taken as an endorsement of the use of the
Read class for any purpose, nor as an endorsement of its continued
existence in the standard library.


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


[Haskell-cafe] Re: Exception handling in numeric computations

2009-03-27 Thread Jonathan Cast
On Fri, 2009-03-27 at 12:24 +, Chris Kuklewicz wrote:
> Jonathan Cast wrote:
> > Sure.  Which also points out that the original safeDiv wasn't actually
> > safe, since there's no guarantee of what evaluate will do with x and y.
> > (Actually, there's not much guarantee of what evaluate does anyway ---
> > just that any errors in e's definition get turned into exceptions by the
> > time evaluate e finishes running, or don't turn into exceptions at all).
> > 
> 
> That is not true if you mean "any errors" as "any and all errors".

No, that's not what I mean.  I just couldn't think of a good phrasing
for `errors that would prevent e from being evaluated to HNF'.  Which is
still a lousy phrasing.

jcc


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


Re: [Haskell-cafe] Re: Exception handling in numeric computations

2009-03-26 Thread Jonathan Cast
On Thu, 2009-03-26 at 21:57 -0400, wren ng thornton wrote:
> Jonathan Cast wrote:
> > Xiao-Yong Jin wrote:
> > > > Xiao-Yong Jin wrote:
> > > > > So I have another question.  Is the following function safe
> > > > > and legitimate?
> > > > >
> > > > >> safeDiv :: (Exception e, Integral a) =>
> > > > >>a -> a -> Either e a
> > > > >> safeDiv x y = unsafePerformIO . try . evaluate $ div x y
> > >
> > >> safeDiv' :: (Exception e, Integral a) =>
> > >> a -> a -> Either e a
> > >> safeDiv' _ 0 = Left e
> > >> safeDiv' x y = Right $ div x y
> > 
> > [...]
> > Other than that, I think the imprecise exceptions paper guarantees that
> > these two functions are equivalent (albeit unwisely: see below).
> 
> I don't think so. The evaluation of x and y may throw errors before we 
> get around to div.

Sure.  Which also points out that the original safeDiv wasn't actually
safe, since there's no guarantee of what evaluate will do with x and y.
(Actually, there's not much guarantee of what evaluate does anyway ---
just that any errors in e's definition get turned into exceptions by the
time evaluate e finishes running, or don't turn into exceptions at all).

> * safeDiv' will evaluate y (to pattern match against 0) and may return 
> an error, e, whereas safeDiv will return Left e if div is strict in y.
> 
> * safeDiv' postpones evaluating x and so may return Right e, whereas 
> safeDiv will return Left e if div is strict in x.

jcc


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


Re: [Haskell-cafe] an OS-independent executeFile??

2009-03-26 Thread Jonathan Cast
On Thu, 2009-03-26 at 17:27 -0500, Vasili I. Galchin wrote:
> ok .. how about API independent? ;^)

Last I checked VMS, OS/360 (NB: not dead by a long shot), etc. had APIs
too.

What you really mean is `does not break when run against Windows's
pseudo-POSIX API despite Microsoft's best efforts' :)

jcc


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


Re: [Haskell-cafe] an OS-independent executeFile??

2009-03-26 Thread Jonathan Cast
On Thu, 2009-03-26 at 17:16 -0500, Vasili I. Galchin wrote:
> Hello,
> 
>   I have been looking through Hackage and using Hoogle to "fork
> and execute" a program in an OS-independent way, i.e. neutral from
> POSIX and Win32 APIs. Does such a library function exist?

System.Process.createProcess
( 
http://haskell.org/ghc/docs/latest/html/libraries/process/System-Process.html#v%3AcreateProcess
 ) works on both Unix and Windows.[1]

jcc

[1] This is not the same as OS-independent!


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


Re: mapM as a Space Leak (Was: [Haskell-cafe] about Haskell code written to be "too smart")

2009-03-26 Thread Jonathan Cast
On Thu, 2009-03-26 at 12:29 -0700, Thomas Hartman wrote:
> > I wonder if JHC
> > or some other compiler might work better with these examples?
> 
> Are you saying that different compilers might give different answers?
> 
> Yikes!
> 
> Too clever indeed!

No, they might produce code with different performance characteristics.

Which is very much what you want; there is no way to compile Haskell
such that reasonable-looking code is

 a) Fast and
 b) Predictably performant.

The idea of Haskell is to abstract away from the predictable performance
of the code by a) using a good compiler, and b) putting absolute
un-questioning faith in your profiler.

jcc


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


Re: [Haskell-cafe] Re: Exception handling in numeric computations

2009-03-26 Thread Jonathan Cast
On Thu, 2009-03-26 at 14:23 -0400, Xiao-Yong Jin wrote:
> Henning Thielemann  writes:
> 
> > On Thu, 26 Mar 2009, Xiao-Yong Jin wrote:
> >
> >> So I have another question.  Is the following function safe
> >> and legitimate?
> >>
> >>> safeDiv :: (Exception e, Integral a) =>
> >>>a -> a -> Either e a
> >>> safeDiv x y = unsafePerformIO . try . evaluate $ div x y
> >>
> >> I believe it should be okay to use this 'safeDiv'.  What do
> >
> > I think that question is wrong way around. The real question is, why
> > do you want to solve your problem using unsafePerformIO?
> 
> I just want to know, from a theoretical point of view,
> whether this 'safeDiv' in above definition is the same as
> 
> > safeDiv' :: (Exception e, Integral a) =>
> > a -> a -> Either e a
> > safeDiv' _ 0 = Left e
> > safeDiv' x y = Right $ div x y

You need some sort of type case here to make sure your first case
matches only if e is the right type for divide-by-zero errors (too lazy
to look it up atm).  Alternatively, you could replace your type variable
e with the actual exception type you want, here and in the
unsafePerformIO version.

Other than that, I think the imprecise exceptions paper guarantees that
these two functions are equivalent (albeit unwisely: see below).

> For the question why do I want to do that, I am not sure.  I
> guess if the function which has an error call inside is
> provided by other library package, and I don't have a clear
> and easy way to tell whether the function will make the
> error call or not, it would be easy just to make a wrapper
> like that.

It might be easy, but if you didn't have a lot of insight into the
function's behavior, then it would be difficult to tell whether it's
really going to call error or whether it's going to go off into an
infinite loop.  (Consider the (slow) definition

x ^ n | n == 0= 1
  | n <  0= error "Negative exponents require ^^"
  | otherwise = x * x ^ (n - 1)

Now consider what happens if the library function forgets the second
case.  Your wrapper isn't safe anymore!)

I can see only two cases where a library function could call error
sometimes, and you wouldn't have a good feel for when:

 a) The function is calling error on exceptions.  You should bug the
library author to put the function into an exception monad instead.
Devil-may-care users can use

either (error . show) id

to turn exceptions into errors.

 b) The function has explicit pre-conditions, which you don't
understand.  You shouldn't pass arguments to a function that violate its
pre-conditions (ever!); if you don't understand those preconditions well
enough to test them in Haskell code, you might not understand them well
enough to make sure your code is calling the function correctly.  So you
might want to study the preconditions a little more.

> It's also a possible situation that I don't know
> how to test the input to a foreign function call.

FFI calls cannot throw Haskell exceptions.

jcc


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


Re: [Haskell-cafe] Use unsafePerformIO to catch Exception?

2009-03-25 Thread Jonathan Cast
On Wed, 2009-03-25 at 22:32 +0100, Henning Thielemann wrote:
> On Wed, 25 Mar 2009, Jonathan Cast wrote:
> 
> > On Wed, 2009-03-25 at 07:39 -0400, Xiao-Yong Jin wrote:
> >>
> >> Could you elaborate more about why this kind of breakage
> >> wouldn't happen if 'try' is used in an IO monad as intended?
> >
> > It would.  But it would happen in IO, which is allowed to be
> > non-deterministic.  Pure Haskell is not allowed to be non-deterministic.
> 
> In my opinion, 'try' catching 'error's is still a hack, since 'error's aka 
> bottom mean programming error. Thus catching them is debugging, bug hiding 
> or something worse, but not exception handling.

100% agreed.  The nice thing about the extensible exceptions is that you
*can* decline to handle ErrorCall `exceptions'; but errors caught by try
should be viewed analogously to signals or asynchronous exceptions.  The
RTS sometimes detects a bug and (sometimes!) stops execution with an
exception; the user sometimes detects the bug and (sometimes!) stops
execution with SIGINT.  The most you can do is try to limit the amount
of secondary damage and give the programmer the best clue where to start
hunting.

jcc


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


Re: [Haskell-cafe] [ANN] ansi-terminal, ansi-wl-pprint - ANSI terminal support for Haskell

2009-03-25 Thread Jonathan Cast
On Wed, 2009-03-25 at 21:18 +, Andrew Coppin wrote:
> I'M ON WINDOWS! ;-)

We've noticed...

jcc


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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-25 Thread Jonathan Cast
On Wed, 2009-03-25 at 12:48 -0700, Dan Weston wrote:
> > However, there is something to be said for code that just looks like a
>  > duck and quacks like a duck. It's less likely to surprise you.
>  >
>  > So... I insist... Easy for a beginner to read == better!
> 
> All you have said is that one building a skyscraper will need 
> scaffolding, blueprints, and a good building inspector. The intended 
> inhabitants of that skyscraper will not want to stare out at scaffolding 
> for the rest of their lives.

+1

jcc


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


Re: [Haskell-cafe] Use unsafePerformIO to catch Exception?

2009-03-25 Thread Jonathan Cast
On Wed, 2009-03-25 at 10:00 -0700, Donn Cave wrote:
> Quoth Jonathan Cast :
> > On Wed, 2009-03-25 at 09:15 -0700, Donn Cave wrote:
> 
> >> OK, these are interesting phenomena.  From a practical point of view,
> >> though, I could see someone weighing the potential costs and benefits
> >> of a exception handler outside IO like this, and these effects might
> >> not even carry all that much weight.
> >
> > Well, sure.  From a purely `practical' point of view, I don't know why
> > you would even use a purely functional language (as opposed to trying to
> > minimize side effects in an impure language).  But if you're not
> > concerned about purity, or ease of equational reasoning, or accuracy of
> > a wide range of compiler transformations/optimizations/because it makes
> > the generated code pretty to sort the formal parameters by name before
> > forcing them-implementation decisions, then please do not use Haskell.
> > There are many other languages that are suitable for what you want to
> > do, and it would be a courtesy to those of us who *do* use Haskell
> > because it is purely functional, not to have to explicitly exclude your
> > library from our picture of the language's capabilities.
> 
> Concerned about purity, ease of equational reasoning, etc.?  Sure ...
> but I guess hoping we can agree on practical reasons for interest in
> these things, as opposed to, or at least in addition to, their esthetic
> or religious appeal.  I'm guessing you would likewise,

Nope.  You must not have been following my positions in previous
discussions.  I am committed to functional purity for its own sake (just
as I am committed to software development for its own sake; don't you
*dare* suggest using Global Script!)

> if only because
> a solely esthetic appeal is difficult angle to pursue because people's
> esthetic sensibilities aren't guaranteed to line up very well.  And in
> fact the way I read the responses so far in this thread, the range of
> attitudes towards the matter seems pretty wide to me, among people whose
> views I respect.

> So I thought it would be interesting to explore statements like "you
> must not do this", and "pure Haskell is not allowed to be
> non-deterministic", in terms of practical effects.  No one would
> make a statement like that and not hope to be challenged on it?

What?  Challenged by people who think Haskell should not be a purely
functional language?  I mean, that's kind of what it is.  Again, if you
don't want to use a purely functional language, there are *lots* of
impure languages out there.  There's no need to turn Haskell into one of
them.

jcc


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


Re: [Haskell-cafe] Use unsafePerformIO to catch Exception?

2009-03-25 Thread Jonathan Cast
On Wed, 2009-03-25 at 09:15 -0700, Donn Cave wrote:
> Quoth Lennart Augustsson :
> 
> > Some examples of what might happen:
> 
> OK, these are interesting phenomena.  From a practical point of view,
> though, I could see someone weighing the potential costs and benefits
> of a exception handler outside IO like this, and these effects might
> not even carry all that much weight.

Well, sure.  From a purely `practical' point of view, I don't know why
you would even use a purely functional language (as opposed to trying to
minimize side effects in an impure language).  But if you're not
concerned about purity, or ease of equational reasoning, or accuracy of
a wide range of compiler transformations/optimizations/because it makes
the generated code pretty to sort the formal parameters by name before
forcing them-implementation decisions, then please do not use Haskell.
There are many other languages that are suitable for what you want to
do, and it would be a courtesy to those of us who *do* use Haskell
because it is purely functional, not to have to explicitly exclude your
library from our picture of the language's capabilities.

jcc


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


Re: [Haskell-cafe] Re: about Haskell code written to be "too smart"

2009-03-25 Thread Jonathan Cast
On Wed, 2009-03-25 at 15:32 +, Simon Marlow wrote:
> Jonathan Cast wrote:
> > On Wed, 2009-03-25 at 15:09 +, Simon Marlow wrote:
> >> the ordering that the state monad expects 
> >> (and I can never remember which way around they are in 
> >> Control.Monad.State).
> > 
> > Really?  I found it obvious once I figured out it how simple it made
> > (>>=).  With the order from Control.Monad.State (with constructors
> > ignored):
> > 
> > a >>= f = \ s -> case s a of
> >(x, s') -> f x s'
> > 
> > Reversing the order of the components of the result gives you
> > 
> > a >>= f = \ s -> case s a of
> > (s', x) -> f x s'
> > 
> > which just looks weird.
> 
> It might look weird to you, but that's the way that GHC's IO and ST monads 
> do it.  It looks perfectly natural to me!

Right.  Consider this an argument for fixing IO/ST(/STM?) to conform to
the self-evidently correct ordering of Control.Monad.State :)

> (and you have the a and s the 
> wrong way around in 'case s a', BTW).

Um, yes.  /Mea culpa/.

> >> Try doing it with mapAccumL, which is arguably the right abstraction,
> >> but 
> >> has the components the other way around.
> > 
> > Define
> > 
> > swap (a, b) = (b, a)
> 
> ew, that's far too crude.  I think you mean
> 
>swap = uncurry $ flip (,)

Ah, yes.

jcc


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


Re: [Haskell-cafe] Re: about Haskell code written to be "too smart"

2009-03-25 Thread Jonathan Cast
On Wed, 2009-03-25 at 03:01 +, Robin Green wrote:
> On Wed, 25 Mar 2009 08:25:40 -0700
> Jonathan Cast  wrote:
> 
> > Define
> > 
> > swap (a, b) = (b, a)
> 
> By the way, if you want to be "too smart", there's a generalised
> version of swap in Control.Category.Braided in the category-extras
> package.

Thanks, I'll check it out.

> That might be a bit overkill though.

What is this word `overkill' you use?

jcc


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


Re: [Haskell-cafe] Re: about Haskell code written to be "too smart"

2009-03-25 Thread Jonathan Cast
On Wed, 2009-03-25 at 15:09 +, Simon Marlow wrote:
> the ordering that the state monad expects 
> (and I can never remember which way around they are in Control.Monad.State).

Really?  I found it obvious once I figured out it how simple it made
(>>=).  With the order from Control.Monad.State (with constructors
ignored):

a >>= f = \ s -> case s a of
   (x, s') -> f x s'

Reversing the order of the components of the result gives you

a >>= f = \ s -> case s a of
(s', x) -> f x s'

which just looks weird.

> Try doing it with mapAccumL, which is arguably the right abstraction,
> but 
> has the components the other way around.

Define

swap (a, b) = (b, a)

You'll never worry about the order of components of a pair again.  This
function is as indispensable as flip.

jcc


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


Re: [Haskell-cafe] Use unsafePerformIO to catch Exception?

2009-03-25 Thread Jonathan Cast
On Wed, 2009-03-25 at 07:39 -0400, Xiao-Yong Jin wrote:
> Jonathan Cast  writes:
> 
> > On Tue, 2009-03-24 at 23:13 -0700, Donn Cave wrote:
> >> Quoth Duncan Coutts :
> >> 
> >> > You must not do this. It breaks the semantics of the language.
> >> >
> >> > Other people have given practical reasons why you should not but a
> >> > theoretical reason is that you've defined a non-continuous function.
> >> > That is impossible in the normal semantics of pure functional languages.
> >> > So you're breaking a promise which we rely on.
> >> 
> >> Could you elaborate a little, in what sense are we (?) relying on it?
> >> 
> >> I actually can't find any responses that make a case against it on a
> >> really practical level - I mean, it seems to be taken for granted that
> >> it will work as intended,
> >
> > It shouldn't be.
> >
> > Consider:
> >
> > loop = loop
> > blam = error "blam"
> > notReallyTry = unsafePerformIO . try . evaluate
> >
> > Now, normally, we have, for all x, y,
> >
> >   x `seq` y `seq` x
> > = y `seq` x
> >
> > But we clearly do *not* have this for x = blam, y = loop, since the
> > equality isn't preserved by notReallyTry:
> >
> > notReallyTry $ blam `seq` loop `seq` blam = Left (ErrorCall "blam")
> > notReallyTry $ loop `seq` blam= loop
> >
> > Now, say a compiler sees the definition
> >
> > foo x y = x `seq` y `seq` x
> >
> > in one module, and then in a later one
> >
> > expectToBeTotal = notReallyTry $ foo blam loop
> >
> > ?  What happens if the compiler, while compiling foo, notices that x is
> > going to be evaluated eventually anyway, and decides against forcing it
> > before y?
> >
> > What if foo was written as
> >
> > foo (!x) (!y) = x
> >
> > ?  Which order are the evaluations performed in?  In a purely functional
> > language, it doesn't matter; but all of a sudden with impure operations
> > like notReallyTry popping up, it does.
> 
> Could you elaborate more about why this kind of breakage
> wouldn't happen if 'try' is used in an IO monad as intended?

It would.  But it would happen in IO, which is allowed to be
non-deterministic.  Pure Haskell is not allowed to be non-deterministic.

jcc


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


Re: [Haskell-cafe] Use unsafePerformIO to catch Exception?

2009-03-24 Thread Jonathan Cast
On Tue, 2009-03-24 at 23:13 -0700, Donn Cave wrote:
> Quoth Duncan Coutts :
> 
> > You must not do this. It breaks the semantics of the language.
> >
> > Other people have given practical reasons why you should not but a
> > theoretical reason is that you've defined a non-continuous function.
> > That is impossible in the normal semantics of pure functional languages.
> > So you're breaking a promise which we rely on.
> 
> Could you elaborate a little, in what sense are we (?) relying on it?
> 
> I actually can't find any responses that make a case against it on a
> really practical level - I mean, it seems to be taken for granted that
> it will work as intended,

It shouldn't be.

Consider:

loop = loop
blam = error "blam"
notReallyTry = unsafePerformIO . try . evaluate

Now, normally, we have, for all x, y,

  x `seq` y `seq` x
= y `seq` x

But we clearly do *not* have this for x = blam, y = loop, since the
equality isn't preserved by notReallyTry:

notReallyTry $ blam `seq` loop `seq` blam = Left (ErrorCall "blam")
notReallyTry $ loop `seq` blam= loop

Now, say a compiler sees the definition

foo x y = x `seq` y `seq` x

in one module, and then in a later one

expectToBeTotal = notReallyTry $ foo blam loop

?  What happens if the compiler, while compiling foo, notices that x is
going to be evaluated eventually anyway, and decides against forcing it
before y?

What if foo was written as

foo (!x) (!y) = x

?  Which order are the evaluations performed in?  In a purely functional
language, it doesn't matter; but all of a sudden with impure operations
like notReallyTry popping up, it does.

jcc


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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Jonathan Cast
On Tue, 2009-03-24 at 16:43 -0700, Donn Cave wrote:
> If he really intended to promote some dumb code as a better
> alternative to some otherwise equivalent smart code,

`Smart' is Manlio's term --- or, rather, his characterization of his
friends' reaction upon seeing some inscrutable piece of (apparent)
Haskell golf or (seemingly) pointless code.  The code seems excessively
clever to them; when Manlio's example is merely clear, well-written,
concise, and declarative, rather than operational, in intention.

> ...

> Go ahead and write smart, clearly the benefits outweigh the cost,
> but tell us that there's no cost, no problem here if a reader who
> knows Haskell has a hard time following?

What reader who knows Haskell?  We have a programmer who is,
self-confessedly, just learning Haskell, not really proficient; we have
is friends, who, by his statement of the problem do not know Haskell at
all; and we have some un-specified group of other developers who, by
selection, barely know Haskell or do not know it at all --- that is,
developers who are still in the process of learning.  I think your
``reader who knows Haskel'' has no-where to here figured in the
discussion.

jcc


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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Jonathan Cast
On Tue, 2009-03-24 at 23:15 +0100, Manlio Perillo wrote:
> Dan Piponi ha scritto:
> >> Miguel Mitrofanov wrote:
> >>> takeList = evalState . mapM (State . splitAt)
> > 
> >> However, ironically, I stopped using them for pretty
> >> much the same reason that Manlio is saying.
> > 
> > Are you saying there's a problem with this implementation? It's the
> > only one I could just read immediately. 
> 
> Yes, you understand it immediately once you know what a state monad is.
> But how well is introduced, explained and emphasized the state monad in 
> current textbooks?
> 
> When I started learning Haskell, the first thing I learned was recursion 
> and pattern matching.

You know, this might actually need to be looked into.

You need to know recursion and pattern-matching to *write* re-usable
higher-order functions, but how appropriate is that as the first thing
taught?

jcc


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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Jonathan Cast
On Tue, 2009-03-24 at 22:43 +0100, Manlio Perillo wrote:
> Jonathan Cast ha scritto:
> > [...]
> > 
> > I think, in general, the best way to document the purpose of the
> > function is
> > 
> > -- | Split a function into a sequence of partitions of specified
> > lenth
> > takeList :: [Int] -> [a] -> [[a]]
> > 
> 
> Note that I was not speaking about the best way to document a function.
> 
> I was speaking about the best way to write a function, so that it may 
> help someone who is learning Haskell.

I've already explicitly rejected the claim that professional Haskell
code should be written to aid beginning users.  Again, that's what
textbooks are for.

And I was explicitly commenting on the claim that it was obvious, from
any version posted thus far, what the function was supposed to do.  Your
suggested code hardly helps make the function's purpose clear; comments
(or, better yet, tests, such as:

prop_length = \ ns xn -> sum ns <= length xn ==>
map length (takeList ns xn) == ns

do a much better job of explaining purpose).

jcc


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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Jonathan Cast
On Tue, 2009-03-24 at 22:33 +0300, Eugene Kirpichov wrote:
> Pretty cool once you know what the function does, but I must admit I
> wouldn't immediately guess the purpose of the function when written in
> this way.

I wouldn't immediately guess the purpose of the function written in any
way.

I think, in general, the best way to document the purpose of the
function is

-- | Split a function into a sequence of partitions of specified
lenth
takeList :: [Int] -> [a] -> [[a]]

jcc


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


Re: [Haskell-cafe] about Haskell code written to be "too smart"

2009-03-24 Thread Jonathan Cast
On Tue, 2009-03-24 at 19:42 +0100, Manlio Perillo wrote:
> Tim Newsham ha scritto:
> >> These friends are very interested in Haskell, but it seems that the 
> >> main reason why they don't start to seriously learning it, is that 
> >> when they start reading some code, they feel the "Perl syndrome".
> >>
> >> That is, code written to be "too smart", and that end up being totally 
> >> illegible by Haskell novice.
> >>
> >> I too have this feeling, from time to time.
> >>
> >> Since someone is starting to write the Haskell coding style, I really 
> >> suggest him to take this "problem" into strong consideration.
> > 
> > When you think about it, what you are saying is that Haskell programmers 
> > shouldn't take advantage of the extra tools that Haskell provides. 
> 
> No, I'm not saying this.
> 
> But, as an example, when you read a function like:
> 
> buildPartitions xs ns = zipWith take ns . init $ scanl (flip drop) xs ns
> 
> that can be rewritten (argument reversed) as:
> 
> takeList :: [Int] -> [a] -> [[a]]
> takeList [] _ =  []
> takeList _ [] =  []
> takeList (n : ns) xs  =  head : takeList ns tail
>  where (head, tail) = splitAt n xs

Huh?  This is ugly and un-readable.  Seriously.

> I think that there is a problem.

Damn straight.  It should be:

> buildPartitions xs ns =
> zipWith take ns $ init $ scanl (flip drop) xs ns

Or, if you're really worried about blocks/line, you can increase the
line count a bit (I do this regularly):

> buildPartitions xs ns =
> zipWith take ns $   -- Select just the indicated prefix of
each element
> init $  -- Skip the last (empty) element
> scanl (flip drop) xs $  -- Cumulatively remove prefixes of
indicated length
> ns

> The buildPartition contains too many "blocks".
> And I have read code with even more "blocks" in one line.
> 
> It may not be a problem for a "seasoned" Haskell programmer, but when 
> you write some code, you should never forget that your code will be read 
> by programmers that can not be at your same level.

Not if I can help it.

More seriously, beginner code belongs in the first two-three chapters of
Haskell programming textbooks, not anywhere else.  It's like putting Fun
with Dick & Jane-speak in an adult novel.[1]

> I think that many Haskell programmers forget this detail, and IMHO this 
> is wrong.
> 
> > Haskell provides the ability to abstract code beyond what many other 
> > programming systems allow.  This abstraction gives you the ability to 
> > express things much more tersely.  This makes the code a lot harder to 
> > read for people who are not familiar with the abstractions being used.  
> 
> The problem is that I have still problems at reading and understanding 
> code that is too much terse...
> Because I have to assemble in my mind each block, and if there are too 
> many blocks I have problems.

jcc

[1] Well, not that bad.  Beginner-level code is useful for teaching the
basics of the language; Fun with Dick & Jane is child abuse.


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


Re: [Haskell-cafe] What unsafeInterleaveIO is unsafe

2009-03-18 Thread Jonathan Cast
On Tue, 2009-03-17 at 12:59 +0100, Ketil Malde wrote:
> Duncan Coutts  writes:
> 
> >> [..] I have a sneaking suspicion [exceptions] actually *is* `unsafe'.  Or, 
> >> at
> >> least, incapable of being given a compositional, continuous semantics.
> 
> > Basically if we can only catch exceptions in IO then it doesn't matter,
> > it's just a little extra non-determinism and IO has plenty of that
> > already.
> 
> Couldn't you just substitute "catch exceptions" with "unsafePerformIO"
> here, and make the same argument?

This puzzled me, until I realized you meant `unsafeInterleaveIO'.
That's pretty much the argument that is made for unsafeInterleaveIO.

> Similarly, can't you emulate unsafePerformIO with concurrency?

Assuming you mean unsafeInterleaveIO, not quite.  GHC's scheduler is
fair, so you are guaranteed after

forkIO $ a

that a's side effects will happen eventually.  On the other hand, after

unsafeInterleaveIO $ a

you have basically no guarantee the RTS will ever get around to
scheduling a.  (In fact, if you write it just like that in a do block,
rather than saying

x <- unsafeInterleaveIO $ a

you are pretty much guaranteed that the RTS won't ever feel like
scheduling a.  It'll even garbage collect a without ever executing it.)

> Further, couldn't you, from IO, FFI into a function that examines the
> source code of some pure function, thus being able to differentiate
> funcitions that are normally "indistinguishable"?

Regular IO is good enough for this.

> I've tried to follow this discussion, but I don't quite understand
> what's so bad about unsafeInterleaveIO - or rather, what's so uniquely
> bad about it.  It seems the same issues can be found in every corner
> of IO. 

jcc


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


Re: [Haskell-cafe] What unsafeInterleaveIO is unsafe

2009-03-17 Thread Jonathan Cast
On Tue, 2009-03-17 at 12:40 +, Claus Reinke wrote:
> >> So that first step already relies on IO (where the two are equivalent).
> > Come again?
> 
> The first step in your implication chain was (without the return)
> 
>   throw (ErrorCall "urk!") <= 1
>   ==> evaluate (throw (ErrorCall "urk!")) <= evaluate 1
> 
> but, using evaluation only (no context-sensitive IO), we have
> 
> >> throw (ErrorCall "urk") <= evaluate (throw (ErrorCall "urk"))
> > Sure enough.
> 
> meaning that first step replaced a smaller with a bigger item on the
> smaller side of the inequation.

And the larger side!  I'm trying to determine whether there can exist a
denotational semantics for IO, which treats it as a functor from (D)CPOs
to (D)CPOs, for which the corresponding denotational semantics for the
IO operations satisfies the requirement that they are both monotone and
continuous.  So I assumed monotonicity of evaluate.

> Unless the reasoning includes context-
> sensitive IO rules,

What does this mean again?  I'm working on the assumption that
`context-sensitive' means `under some (not necessarily compositional
and/or continuous and/or monotonic) equivalence relation/

> in which case the IO rule for evaluate brings the
> throw to the top (evaluate (throw ..) -> (throw ..)), making the two
> terms equivalent (modulo IO), and hence the step valid (modulo IO).
> 
> Unless you just rely on
> 
> >But throwIO (ErrorCall "urk") /= _|_:
> >Control.Exception> throwIO (ErrorCall "urk!") `seq` ()
> >()
> 
> in which case that step relies on not invoking IO, so it can't be
> mixed with the later step involving IO for catch (I think).

The IO monad is still a part of Haskell's denotational semantics, right?
Otherwise, I don't think we can really claim Haskell, as a language that
includes IO in its specification, is truly `purely functional'.  It's a
language that integrates two sub-languages, one purely functional and
one side-effectful and imperative.  Which is a nice accomplishment, but
less that what Haskell originally aimed to achieve.

> >> This is very delicate territory. For instance, one might think that
> >> this 'f' seems to define a "negation function" of information content
> >
> >> f x = Control.Exception.catch (evaluate x >> let x = x in x) 
> >> (\(ErrorCall _)->return 0) >>=
> >> print
> >>
> >> and hence violates monotonicity
> >>
> >> (_|_ <= ()) => (f _|_ <= f ())
> >>
> >> since
> >>
> >> *Main> f undefined
> >> 0
> >> *Main> f ()
> >> Interrupted.
> >>
> >> But that is really mixing context-free expression evaluation and
> >> context-sensitive execution of io operations. Most of our favourite
> >> context-free equivalences only hold within the expression evaluation
> >> part, while IO operations are subject to additional, context-sensitive
> >> rules.
> >
> > Could you elaborate on this?  It sounds suspiciously like you're saying
> > Haskell's axiomatic semantics is unsound :: IO.
> 
> Not really unsound, if the separation is observed.

I still don't understand what you're separating.  Are you saying the
semantics of terms of type IO need to be separated from the semantics of
terms of non-IO type?

> One could probably
> construct a non-separated semantics (everything denotational), but at
> the cost of mapping everything to computations rather than values.

So as long as Haskell is no longer pure (modulo lifting everything) it
works?

> Then computations like that 'f' above would, eg, take an extra context
> argument (representing "the world", or at least aspects of the machine
> running the computation), and the missing information needed to take
> 'f _|_'[world] to '()'[world'] would come from that context parameter
> (somewhere in the computational context, there is a representation of
> the computation, which allows the context to read certain kinds of '_|_'
> as exceptions; the IO rule for 'catch' takes that external information and
> injects it back from the computational context into the functional program,
> as data structure representations of exceptions).

> That price is too high, though, as we'd now have to do all reasoning
> in context-sensitive terms which, while more accurate, would bury
> us in irrelevant details. Hence we usually try to use context-free
> reasoning whenever we can get away with it (the non-IO portions
> of Haskell program runs), resorting to context-sensitive reasoning
> only when necessary (the IO steps of Haskell program runs).

So I can't use normal Haskell semantics to reason about IO.  That's
*precisely* what I'm trying to problematize.

> This gives us convenience when the context is irrelevant as well
> as accuracy when the context does matter - we just have to be
> careful when combining the two kinds of reasoning.
> 
> >> For instance, without execution
> >>
> >> *Main> f () `seq` ()
> >> ()
> >> *Main> f undefined `seq` ()
> >> ()
> >>
> >> but if we include execution (and the context-sensitive equivalence
> >> t

Re: categories and monoids (was: Re: [Haskell-cafe] Design Patterns by Gamma or equivalent)

2009-03-17 Thread Jonathan Cast
On Tue, 2009-03-17 at 13:06 +0100, Wolfgang Jeltsch wrote:
> Am Dienstag, 17. März 2009 10:54 schrieben Sie:
> > Wolfgang Jeltsch  writes:
> > > By the way, the documentation of Control.Category says that a category is
> > > a monoid (as far as I remember). This is wrong. Category laws correspond
> > > to monoid laws but monoid composition is total while category composition
> > > has the restriction that the domain of the first argument must match the
> > > codomain of the second. 
> >
> > I'm reading the Barr/Wells slides at the moment, and they say the
> > following:
> >
> > "Thus a category can be regarded as a generalized monoid,
> 
> What is a “generalized monoid”? According to the grammatical construction 
> (adjective plus noun), it should be a special kind of monoid, like a 
> commutative monoid is a special kind of monoid. But then, monoids would be 
> the more general concept and categories the special case, quite the opposite 
> of how it really is.
> 
> A category is not a “generalized monoid” but categories (as a concept) are a 
> generalization of monoids. Each category is a monoid, but not the other way 
> round.

You mean ``each monoid is a category, but not the other way round''.

> A monoid is clearly defined as a pair of a set M and a (total) binary 
> operation over M that is associative and has a neutral element. So, for 
> example, the category of sets and functions is not a monoid. First, function 
> composition is not total if you allow arbitrary functions as its arguments. 
> Second, the collection of all sets is not itself a set (but a true class) 
> which conflicts with the above definition which says that M has to be a set.
> 
> > or a 'monoid with many objects'"
> 
> What is a monoid with many objects?

A categorical definition of a monoid (that is, a plain old boring monoid
in Set) is that it is a category with a single object.  A category is
thus a monoid with the restriction to a single object lifted :)

jcc


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


Re: [Haskell-cafe] What unsafeInterleaveIO is unsafe

2009-03-16 Thread Jonathan Cast
On Tue, 2009-03-17 at 01:16 +, Claus Reinke wrote:
> >> > > "exception handling" which allows to "catch" programming errors.
> >> > And which I have a sneaking suspicion actually *is* `unsafe'.  Or, at
> >> > least, incapable of being given a compositional, continuous semantics.
> >> "A semantics for imprecise exceptions"
> >> http://research.microsoft.com/en-us/um/people/simonpj/papers/imprecise-exn.htm
> >> Basically if we can only catch exceptions in IO then it doesn't matter,
> >> it's just a little extra non-determinism and IO has plenty of that
> >> already.
> >
> > I'm not sure that helps much.  Given the following inequalities (in the
> > domain ordering) and equations:
> >  throw "urk"! <= return 1

Oops, left a superfluous return in there.  I meant

 throw "urk!" <= 1

(The inequality is at Int).

> >  ==> evaluate (throw "urk!") <= evaluate 1
> 
> throw (ErrorCall "urk") <= evaluate (throw (ErrorCall "urk"))

Sure enough.

But throwIO (ErrorCall "urk") /= _|_:

Control.Exception> throwIO (ErrorCall "urk!") `seq` ()
()

> So that first step already relies on IO (where the two are equivalent).

Come again?

> This is very delicate territory. For instance, one might think that
> this 'f' seems to define a "negation function" of information content

> f x = Control.Exception.catch (evaluate x >> let x = x in x) (\(ErrorCall 
> _)->return 0) >>= 
> print
> 
> and hence violates monotonicity
> 
> (_|_ <= ()) => (f _|_ <= f ())
> 
> since
> 
> *Main> f undefined
> 0
> *Main> f ()
> Interrupted.
> 
> But that is really mixing context-free expression evaluation and
> context-sensitive execution of io operations. Most of our favourite
> context-free equivalences only hold within the expression evaluation
> part, while IO operations are subject to additional, context-sensitive
> rules.

Could you elaborate on this?  It sounds suspiciously like you're saying
Haskell's axiomatic semantics is unsound :: IO.

> For instance, without execution
> 
> *Main> f () `seq` ()
> ()
> *Main> f undefined `seq` ()
> ()
> 
> but if we include execution (and the context-sensitive equivalence
> that implies, lets call it ~),

So

   a ~ b = `The observable effects of $(x) and $(y) are equal'

?

> we have
> 
> f () ~ _|_ <= return 0 ~ f _|_
> 
> so 'f' shows that wrapping both sides of an inequality in 'catch' need
> not preserve the ordering (modulo ~)

If f _|_ <= f (), then it seems that (<=) is not a (pre-) order w.r.t.
(~).  So taking the quotient of IO Int over (~) gives you a set on which
(<=) is not an ordering (and may not be a relation).

>  - its whole purpose is to recover
> from failure, making something more defined (modulo ~) by translating
> _|_ to something else. Which affects your second implication.

> If the odd properties of 'f' capture the essence of your concerns, I think
> the answer is to keep =, <=, and ~ clearly separate, ideally without losing
> any of the context-free equivalences while limiting the amount of
> context-sensitive reasoning required. If = and ~ are mixed up, however,
> monotonicity seems lost.

So

catch (throwIO e) h ~ h e

but it is not the case that

catch (throwIO e) h = h e

?  That must be correct, actually:

Control.Exception> let x = Control.Exception.catch (throwIO
(ErrorCall "urk!")) (\ (ErrorCall _) -> undefined) in x `seq` ()
()

So catch is total (even if one or both arguments is erroneous), but the
IO executor (a beast totally distinct from the Haskell interpreter, even
if they happen to live in the same body) when executing it feels free to
examine bits of the Haskell program's state it's not safe for a normal
program to inspect.  I'll have to think about what that means a bit
more.

> The semantics in the "imprecise exceptions" paper combines a
> denotational approach for the context-free part with an operational
> semantics

[Totally OT tangent: How did operational semantics come to get its noun?
The more I think about it, the more it seems like a precís of the
implementation, rather than a truly semantic part of a language
specification.]

> for the context-sensitive part. This tends to use the good
> properties of both, with a clear separation between them, but a
> systematic treatment of the resulting identities was left for future work.

jcc


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


Re: [Haskell-cafe] What unsafeInterleaveIO is unsafe

2009-03-16 Thread Jonathan Cast
On Mon, 2009-03-16 at 22:01 +, Duncan Coutts wrote:
> On Mon, 2009-03-16 at 14:17 -0700, Jonathan Cast wrote:
> > On Mon, 2009-03-16 at 22:12 +0100, Henning Thielemann wrote:
> > > On Sun, 15 Mar 2009, Claus Reinke wrote:
> > > 
> > > > import Data.IORef
> > > > import Control.Exception
> > > >
> > > > main = do
> > > >   r <- newIORef 0
> > > >   let v = undefined
> > > >   handle (\(ErrorCall _)->print "hi">>return 42) $ case f v of
> > > > 0 -> return 0
> > > > n -> return (n - 1)
> > > >   y <- readIORef r
> > > >   print y
> > > 
> > > I don't see what this has to do with strictness. It's just the hacky 
> > > "exception handling" which allows to "catch" programming errors.
> > 
> > And which I have a sneaking suspicion actually *is* `unsafe'.  Or, at
> > least, incapable of being given a compositional, continuous semantics.
> 
> See this paper:
> 
> "A semantics for imprecise exceptions"
> http://research.microsoft.com/en-us/um/people/simonpj/papers/imprecise-exn.htm
> 
> Basically if we can only catch exceptions in IO then it doesn't matter,
> it's just a little extra non-determinism and IO has plenty of that
> already.

I'm not sure that helps much.  Given the following inequalities (in the
domain ordering) and equations:

  throw "urk! " <= 1
  evaluate . throw = throwIO
  evaluate x = return x  -- x total
  catch (throwIO a) h = h a
  catch (return x) h = return x

we expect to be able to reason as follows:

  throw "urk"! <= return 1
  ==> evaluate (throw "urk!") <= evaluate 1
  ==> catch (evaluate (throw "urk!")) (const $ return 2) <= catch
(evaluate 1) (const $ return 2)

while

catch (evaluate (throw "urk!")) (const $ return 2)
  = catch (throwIO "urk!") (const $ return 2)
  = const (return 2) "urk!"
  = return 2

and

catch (evaluate 1) (const $ return 2)
  = catch (return 1) (const $ return 2)
  = return 1

So return 2 <= return 1, in the domain ordering?  That doesn't seem
right.

jcc


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


Re: [Haskell-cafe] What unsafeInterleaveIO is unsafe

2009-03-16 Thread Jonathan Cast
On Mon, 2009-03-16 at 22:12 +0100, Henning Thielemann wrote:
> On Sun, 15 Mar 2009, Claus Reinke wrote:
> 
> > import Data.IORef
> > import Control.Exception
> >
> > main = do
> >   r <- newIORef 0
> >   let v = undefined
> >   handle (\(ErrorCall _)->print "hi">>return 42) $ case f v of
> > 0 -> return 0
> > n -> return (n - 1)
> >   y <- readIORef r
> >   print y
> 
> I don't see what this has to do with strictness. It's just the hacky 
> "exception handling" which allows to "catch" programming errors.

And which I have a sneaking suspicion actually *is* `unsafe'.  Or, at
least, incapable of being given a compositional, continuous semantics.

jcc


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


Re: [Haskell-cafe] What unsafeInterleaveIO is unsafe

2009-03-15 Thread Jonathan Cast
On Sun, 2009-03-15 at 18:11 -0700, Ryan Ingram wrote:
> On Sun, Mar 15, 2009 at 1:56 PM, Jonathan Cast
>  wrote:
> >> But not if you switch the (x <- ...) and (y <- ...) parts:
> >>
> >> main = do
> >> r <- newIORef 0
> >> v <- unsafeInterleaveIO $ do
> >> writeIORef r 1
> >> return 1
> >> y <- readIORef r
> >> x <- case f v of
> >> 0 -> return 0
> >> n -> return (n - 1)
> >> print y
> >>
> >> Now the IORef is read before the case has a chance to trigger the writing.
> >
> > But if the compiler is free to do this itself, what guarantee do I have
> > that it won't?
> 
> You don't really have any guarantee; the compiler is free to assume
> that v is a pure integer and that f is a pure function from integers
> to integers.  Therefore, it can assume that the only observable affect
> of calling f v is non-termination.  Note that unsafeInterleaveIO
> *breaks* this assumption;

[Ignored; begging the question]

jcc


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


Re: [Haskell-cafe] What unsafeInterleaveIO is unsafe

2009-03-15 Thread Jonathan Cast
On Mon, 2009-03-16 at 01:04 +0100, Daniel Fischer wrote:
> Am Montag, 16. März 2009 00:47 schrieb Jonathan Cast:
> > On Mon, 2009-03-16 at 00:14 +0100, Daniel Fischer wrote:
> >
> > > > > However, I understand
> > > > > "unsafeInterleaveIO allows IO computation to be deferred lazily. When
> > > > > passed a value of type IO a, the IO will only be performed when the
> > > > > value of the a is demanded."
> > > >
> > > > Where is this taken from?  If GHC's library docs try to imply that the
> > >
> > > From the documentation of System.IO.Unsafe.
> >
> > This version of those docs:
> >
> >
> > http://haskell.org/ghc/docs/latest/html/libraries/base/System-IO-Unsafe.htm
> >l
> >
> > leaves unsafeInterleaveIO completely un-documented.  So I'm still not
> > sure what you're quoting from.
> 
> The documentation haddock-0.9 built when I compiled ghc-6.8.3 last year.

So it's a GHC (and base) major version out of date.

> > > > programmer can predict when an unsafeInterleaveIO'd operation takes
> > > > place --- well, then they shouldn't.  I'm starting to suspect that not
> > > > starting from a proper denotational theory of IO was a major mistake
> > > > for GHC's IO system (which Haskell 1.3 in part adopted).
> > >
> > > Maybe.
> > >
> > > > > as explicitly allowing the programmer to say "do it if and when the
> > > > > result is needed, not before".
> > > >
> > > > Haskell's order of evaluation is undefined, so this doesn't really
> > > > allow the programmer to constrain when the effects are performed much.
> > >
> > > The full paragraph from the report:
> > >
> > > " The I/O monad used by Haskell mediates between the values natural to a
> > > functional language and the actions that characterize I/O operations and
> > > imperative programming in general. The order of evaluation of expressions
> > > in Haskell is constrained only by data dependencies; an implementation
> > > has a great deal of freedom in choosing this order. Actions, however,
> > > must be ordered in a well-defined manner for program execution -- and I/O
> > > in particular -- to be meaningful. Haskell 's I/O monad provides the user
> > > with a way to specify the sequential chaining of actions, and an
> > > implementation is obliged to preserve this order."
> > >
> > > I read it as saying that IO *does* allow the programmer to control when
> > > the effects are performed.
> >
> > Right.  But by using forkIO or unsafeInterleaveIO you waive that
> > ability.
> 
> That depends on the specification of unsafeInterleaveIO. If it is 
> "unspecified 
> order of evaluation", then yes, if it is "do when needed, not before",

Note that `when needed' is still dependent on the (still unspecified)
(non-IO) Haskell evaluation order.  Also note that, to demonstrate any
strong claims about unsafeInterleaveIO, you need to show that the
compiler *must* perform in such-and-such a way, not simply that it
*will* or that it *may*.

> as my 
> local documentation can be interpreted, then unsafeInterleaveIO reduces that 
> ability, but doesn't completely remove it.

Sure.  The question is whether the compiler has still enough options for
re-ordering the program that transforming a program according to the
standard equational axiomatic semantics for Haskell doesn't change the
set of options the compiler has for the behavior of its generated code.

jcc


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


Re: [Haskell-cafe] What unsafeInterleaveIO is unsafe

2009-03-15 Thread Jonathan Cast
On Mon, 2009-03-16 at 00:14 +0100, Daniel Fischer wrote:
> Am Sonntag, 15. März 2009 23:30 schrieb Jonathan Cast:
> > On Sun, 2009-03-15 at 23:18 +0100, Daniel Fischer wrote:
> > > Am Sonntag, 15. März 2009 22:20 schrieb Jonathan Cast:
> > > > There is *no* guarantee that main0 prints 0, while main1 prints 1, as
> > > > claimed.  The compiler is in fact free to produce either output given
> > > > either program, at its option.  Since the two programs do in fact have
> > > > exactly the same set of possible implementations, they *are*
> > > > equivalent. So the ordering in fact *doesn't* matter.
> > >
> > > Hum. Whether the programme prints 0 or 1 depends on whether "writeIORef r
> > > 1" is done before "readIORef r".
> > > That depends of course on the semantics of IO and unsafeInterleaveIO.
> > >
> > > In so far as the compiler is free to choose there, it can indeed produce
> > > either result with either programme.
> > > But I think
> > > "Haskell 's I/O monad provides the user with a way to specify the
> > > sequential chaining of actions, and an implementation is obliged to
> > > preserve this order." (report, section 7) restricts the freedom
> > > considerably.
> >
> > Why not read that line as prohibiting concurrency (forkIO) as well?
> 
> Good question.
> Because forkIO is a way to explicitly say one doesn't want the one thing 
> necessarily done before the other, I'd say.

As is unsafeInterleaveIO.  (And as is unsafePerformIO, as per the docs:

> If the I/O computation wrapped in unsafePerformIO performs side
> effects, then the relative order in which those side effects take
> place (relative to the main I/O trunk, or other calls to
> unsafePerformIO) is indeterminate.

)

> > > However, I understand
> > > "unsafeInterleaveIO allows IO computation to be deferred lazily. When
> > > passed a value of type IO a, the IO will only be performed when the value
> > > of the a is demanded."
> >
> > Where is this taken from?  If GHC's library docs try to imply that the
> 
> From the documentation of System.IO.Unsafe.

This version of those docs:


http://haskell.org/ghc/docs/latest/html/libraries/base/System-IO-Unsafe.html

leaves unsafeInterleaveIO completely un-documented.  So I'm still not
sure what you're quoting from.

> > programmer can predict when an unsafeInterleaveIO'd operation takes
> > place --- well, then they shouldn't.  I'm starting to suspect that not
> > starting from a proper denotational theory of IO was a major mistake for
> > GHC's IO system (which Haskell 1.3 in part adopted).
> 
> Maybe.
> 
> >
> > > as explicitly allowing the programmer to say "do it if and when the
> > > result is needed, not before".
> >
> > Haskell's order of evaluation is undefined, so this doesn't really allow
> > the programmer to constrain when the effects are performed much.
> 
> The full paragraph from the report:
> 
> " The I/O monad used by Haskell mediates between the values natural to a 
> functional language and the actions that characterize I/O operations and 
> imperative programming in general. The order of evaluation of expressions in 
> Haskell is constrained only by data dependencies; an implementation has a 
> great deal of freedom in choosing this order. Actions, however, must be 
> ordered in a well-defined manner for program execution -- and I/O in 
> particular -- to be meaningful. Haskell 's I/O monad provides the user with a 
> way to specify the sequential chaining of actions, and an implementation is 
> obliged to preserve this order."
> 
> I read it as saying that IO *does* allow the programmer to control when the 
> effects are performed.

Right.  But by using forkIO or unsafeInterleaveIO you waive that
ability.

> > > So I think main0 *must* print 0, because the ordering of the statements
> > > puts the reading of the IORef before the result of the
> > > unsafeInterleaveIOed action may be needed, so an implementation is
> > > obliged to read it before writing to it.
> > >
> > > In main1 however, v may be needed to decide what action's result x is
> > > bound to, before the reading of the IORef in the written order, so if f
> > > is strict, the unsafeInterleaveIOed action must be performed before the
> > > IORef is read and the programme must print 1,
> >
> > Although as Ryan pointed out, the compiler may decide to omit the case
> > statement entirely, if it can statically prove that f v is undefined.
> 
> I suppose that's a typo and should be "unneeded".
> But can it prove that f v is unneeded? After all, it may influence whether 0 
> or 1 is printed.

[Ignored: begging the question]

jcc


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


Re: [Haskell-cafe] What unsafeInterleaveIO is unsafe

2009-03-15 Thread Jonathan Cast
On Sun, 2009-03-15 at 23:18 +0100, Daniel Fischer wrote:
> Am Sonntag, 15. März 2009 22:20 schrieb Jonathan Cast:
> > There is *no* guarantee that main0 prints 0, while main1 prints 1, as
> > claimed.  The compiler is in fact free to produce either output given
> > either program, at its option.  Since the two programs do in fact have
> > exactly the same set of possible implementations, they *are* equivalent.
> > So the ordering in fact *doesn't* matter.
> 
> Hum. Whether the programme prints 0 or 1 depends on whether "writeIORef r 1" 
> is done before "readIORef r".
> That depends of course on the semantics of IO and unsafeInterleaveIO.

> In so far as the compiler is free to choose there, it can indeed produce 
> either result with either programme.
> But I think
> "Haskell 's I/O monad provides the user with a way to specify the sequential 
> chaining of actions, and an implementation is obliged to preserve this 
> order." (report, section 7) restricts the freedom considerably.

Why not read that line as prohibiting concurrency (forkIO) as well?

> However, I understand
> "unsafeInterleaveIO allows IO computation to be deferred lazily. When passed 
> a 
> value of type IO a, the IO will only be performed when the value of the a is 
> demanded."

Where is this taken from?  If GHC's library docs try to imply that the
programmer can predict when an unsafeInterleaveIO'd operation takes
place --- well, then they shouldn't.  I'm starting to suspect that not
starting from a proper denotational theory of IO was a major mistake for
GHC's IO system (which Haskell 1.3 in part adopted).

> as explicitly allowing the programmer to say "do it if and when the result is 
> needed, not before".

Haskell's order of evaluation is undefined, so this doesn't really allow
the programmer to constrain when the effects are performed much.

> So I think main0 *must* print 0, because the ordering of the statements puts 
> the reading of the IORef before the result of the unsafeInterleaveIOed action 
> may be needed, so an implementation is obliged to read it before writing to 
> it.

> In main1 however, v may be needed to decide what action's result x is bound 
> to, before the reading of the IORef in the written order, so if f is strict, 
> the unsafeInterleaveIOed action must be performed before the IORef is read 
> and the programme must print 1,

Although as Ryan pointed out, the compiler may decide to omit the case
statement entirely, if it can statically prove that f v is undefined.

>  but if f is lazy, v is not needed for that 
> decision, so by the documentation, the unsafeInterleaveIOed action will not 
> be performed, and the programme prints 0.

jcc


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


Re: [Haskell-cafe] What unsafeInterleaveIO is unsafe

2009-03-15 Thread Jonathan Cast
On Sun, 2009-03-15 at 22:09 +0100, Daniel Fischer wrote:
> Am Sonntag, 15. März 2009 21:56 schrieb Jonathan Cast:
> > On Sun, 2009-03-15 at 21:43 +0100, Daniel Fischer wrote:
> > > Am Sonntag, 15. März 2009 21:25 schrieb Jonathan Cast:
> > > > On Sun, 2009-03-15 at 13:02 -0700, Ryan Ingram wrote:
> > > > > Furthermore, due to the monad laws, if f is total, then reordering
> > > > > the (x <- ...) and (y <- ...) parts of the program should have no
> > > > > effect. But if you switch them, the program will *always* print 0.
> > > >
> > > > I'm confused.  I though if f was strict, then my program *always*
> > > > printed 1?
> > >
> > > But not if you switch the (x <- ...) and (y <- ...) parts:
> > >
> > > main = do
> > > r <- newIORef 0
> > > v <- unsafeInterleaveIO $ do
> > > writeIORef r 1
> > > return 1
> > > y <- readIORef r
> > > x <- case f v of
> > > 0 -> return 0
> > > n -> return (n - 1)
> > > print y
> > >
> > > Now the IORef is read before the case has a chance to trigger the
> > > writing.
> >
> > But if the compiler is free to do this itself, what guarantee do I have
> > that it won't?
> >
> 
> None?
> 
> Wasn't that Ryan's point, that without the unsafeInterleaveIO, that 
> reordering 
> wouldn't matter, but with it, it does?

Sure.  But *that point is wrong*.  Given the two programs

main0 = do
r <- newIORef 0
v <- unsafeInterleaveIO $ do
writeIORef r 1
return 1
y <- readIORef r
x <- case f v of
0 -> return 0
n -> return (n - 1)
print y

main1 = do
r <- newIORef 0
v <- unsafeInterleaveIO $ do
writeIORef r 1
return 1
x <- case f v of
0 -> return 0
n -> return (n - 1)
y <- readIORef r
print y

There is *no* guarantee that main0 prints 0, while main1 prints 1, as
claimed.  The compiler is in fact free to produce either output given
either program, at its option.  Since the two programs do in fact have
exactly the same set of possible implementations, they *are* equivalent.
So the ordering in fact *doesn't* matter.

jcc


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


Re: [Haskell-cafe] What unsafeInterleaveIO is unsafe

2009-03-15 Thread Jonathan Cast
On Sun, 2009-03-15 at 21:43 +0100, Daniel Fischer wrote:
> Am Sonntag, 15. März 2009 21:25 schrieb Jonathan Cast:
> > On Sun, 2009-03-15 at 13:02 -0700, Ryan Ingram wrote:
> >
> > > Furthermore, due to the monad laws, if f is total, then reordering the
> > > (x <- ...) and (y <- ...) parts of the program should have no effect.
> > > But if you switch them, the program will *always* print 0.
> >
> > I'm confused.  I though if f was strict, then my program *always*
> > printed 1?
> 
> But not if you switch the (x <- ...) and (y <- ...) parts:
> 
> main = do
> r <- newIORef 0
> v <- unsafeInterleaveIO $ do
> writeIORef r 1
> return 1
> y <- readIORef r
> x <- case f v of
> 0 -> return 0
> n -> return (n - 1)
> print y
> 
> Now the IORef is read before the case has a chance to trigger the writing.

But if the compiler is free to do this itself, what guarantee do I have
that it won't?

jcc


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


Re: [Haskell-cafe] What unsafeInterleaveIO is unsafe

2009-03-15 Thread Jonathan Cast
On Sun, 2009-03-15 at 13:02 -0700, Ryan Ingram wrote:
> unsafeInterleaveIO allows embedding side effects into a pure
> computation.  This means you can potentially observe if some pure
> value has been evaluated or not;  the result of your code could change
> depending how lazy/strict it is, which is very hard to predict!
> 
> For example:
> 
> > -- given
> > f :: Integer -> Integer
> >
> > main = do
> > r <- newIORef 0
> > v <- unsafeInterleaveIO $ do
> > writeIORef r 1
> > return 1
> > x <- case f v of
> > 0 -> return 0
> > n -> return (n - 1)
> > y <- readIORef r
> > print y
> >
> > -- a couple of examples:
> > f x = 0 -- program prints "0"
> > -- f x = x -- program prints "1"
> 
> "f" is pure.  But if f is nonstrict, this program prints 0, and if
> it's strict, it prints 1.  The strictness of a pure function can
> change the observable behavior of your program!

Right.  If the compiler feels like changing the way it implements your
program based on that factor.  But `semantics' that the compiler doesn't
preserve are kind of useless...

> Furthermore, due to the monad laws, if f is total, then reordering the
> (x <- ...) and (y <- ...) parts of the program should have no effect.
> But if you switch them, the program will *always* print 0.

I'm confused.  I though if f was strict, then my program *always*
printed 1?

> Also, the compiller might notice that x is never used, and that "f" is
> total.  So it could just optimize out the evaluation of "f v"
> completely, at which point the program always prints 0 again; changing
> optimization settings modifies the result of the program.
> 
> This is why unsafeInterleaveIO is unsafe.

Well, unsafeInterleaveIO or reasoning based on overly specific
assumptions about how things must be implemented, anyway.  I'm not sure
you've narrowed it down to usafeInterleaveIO, though.

jcc


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


Re: [Haskell-cafe] Pointless functors

2009-03-13 Thread Jonathan Cast
On Sat, 2009-03-14 at 02:12 +1000, Matthew Brecknell wrote:
> Ross Paterson wrote: 
> > No.  Choose an arbitrary element shape :: f () and define
> >point x = fmap (const x) shape
> 
> Interesting. Is the arbitrariness of the shape some sort of evidence
> that Pointed is not really a very useful class in its own right?

A simpler bit of evidence is that the only law I can think of for point
(in its own right) is

  fmap f . point = point . f

which we get free anyway.

jcc


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


Re: [Haskell-cafe] Parsing floating point numbers

2009-03-08 Thread Jonathan Cast
On Sun, 2009-03-08 at 19:34 -0500, Bjorn Buckwalter wrote:
> Hi all,
> 
> What is your preferred method of parsing floating point numbers (from
> String to Float/Double)? Parsec it seems only does positive floats out
> of the box and PolyParse requires the float to be on scientific form
> (exponential). While I've worked around these shortcomings in the past
> I feel that I am reinventing the wheel as surely I am not the only to
> run into these limitations. How do you parse your floats? Can you
> recommend a parsing library that handles them solidly?
> 
> (For my current needs the formats accepted by "read" are sufficient,
> but I want reasonable error handling (Maybe or Either) instead of an
> exception on bad inputs.)

  fmap fst . listToMaybe . reads

jcc


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


Re: [Haskell-cafe] do you have to use fix with forkio?

2009-03-05 Thread Jonathan Cast
On Thu, 2009-03-05 at 15:36 -0800, Daryoush Mehrtash wrote:
> In this chat server implementation
> http://www.haskell.org/haskellwiki/Implement_a_chat_server
> 
> forkIO is used with fix as in:
> 
> reader <- forkIO $ fix $ \loop -> do
> 
> (nr', line) <- readChan chan'
> when (nr /= nr') $ hPutStrLn hdl line
> 
> loop
> 
> Do you have to use fix?  Or is there a way to write this with a "let"?

You can certainly use let:

  reader <- forkIO $ let loop = do
  (nr', line) <- readChan chan'
  when (nr /= nr') $ hPutStrLn hdl line
  loop
in loop

But the version with fix is clearer (at least to people who have fix in
their vocabulary) and arguably better style.

jcc


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


Re: [Haskell-cafe] Re: [Haskell] Lazy IO breaks purity

2009-03-05 Thread Jonathan Cast
On Thu, 2009-03-05 at 13:08 +, Simon Marlow wrote:
> Lennart Augustsson wrote:
> > I don't see any breaking of referential transparence in your code.
> > Every time you do an IO operation the result is basically
> > non-deterministic since you are talking to the outside world.
> > You're assuming the IO has some kind of semantics that Haskell makes
> > no promises about.
> > 
> > I'm not saying that this isn't a problem, because it is.
> > But it doesn't break referential transparency, it just makes the
> > semantics of IO even more complicated.
> > 
> > (I don't have a formal proof that unsafeInterleaveIO cannot break RT,
> > but I've not seen an example where it does yet.)
> 
> So the argument is something like: we can think of the result of a call to 
> unsafeInterleaveIO as having been chosen at the time we called 
> unsafeInterleaveIO, rather than when its result is actually evaluated. 
> This is on dodgy ground, IMO: either you admit that the IO monad contains 
> an Oracle, or you admit it can time-travel.   I don't believe in either of 
> those things :-)

That's the charm of denotational semantics --- you're outside the laws
of physics.

jcc


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


Re: [Haskell-cafe] Theory about uncurried functions

2009-03-03 Thread Jonathan Cast
On Wed, 2009-03-04 at 01:35 +0100, Henning Thielemann wrote:
> On Tue, 3 Mar 2009, Peter Verswyvelen wrote:
> 
> > Now, does a similar theory exist of functions that always have one
> > input and one output, but these inputs and outputs are *always*
> > tuples? Or maybe this does not make any sense?
> 
> I don't think one can forbid currying.

Sure you can, just work in a category with finite products (and possibly
finite co-products) but not exponentials.  Of course, then your language
is first order --- and this doesn't do anything to stop partial
application, which is still easy --- but it's quite possible.

jcc


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


Re: [Haskell-cafe] Re: statep haskell-lang [was: Re: Hoogle and Network.Socket]

2009-02-26 Thread Jonathan Cast
On Thu, 2009-02-26 at 22:34 -0500, Brandon S. Allbery KF8NH wrote:
> There's something I'm missing in all of this.
> 
> Perl is in the process of rebooting itself (perl6 is syntactically  
> very different from perl5; the closest it's ever previously gotten to  
> this kind of radical change was the change from ' to :: as the package  
> separator).  Perl5 will continue to exist, and probably even be  
> maintained.  So why is it not possible to declare Haskell98 and  
> Haskell10 (or whatever Haskell' becomes) as stable, maintained  
> languages for production use, then reboot the Haskell development  
> process?

Right, that's what I want.  (Although perl6 has been a long time in
coming).  Haskell is, far and away, the best name I can think of for the
next mainstream research language.  I just don't think it's going to
happen.

> In fact, I thought that was the reason Haskell98 support is  
> retained in Haskell compilers?

jcc


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


Re: [Haskell-cafe] Re: statep haskell-lang [was: Re: Hoogle and Network.Socket]

2009-02-26 Thread Jonathan Cast
On Fri, 2009-02-27 at 00:04 +0100, Achim Schneider wrote:
> Jonathan Cast  wrote:
> > (I am actually writing my own language;
> > when I get something usable for real work, I may very well just plain
> > un-subscribe from haskell-cafe, even though I will continue using
> > Haskell for bootstrapping for some time after that.)

I've actually got a complete syntax (except the module system (which,
for me, means mostly type classes :)), a type checker (which has lambda
terms --- including higher-order ones --- but no local declarations
yet), and an implementation that seems like it would mostly do what I
want if the standard library were rich enough to write interesting
things in.

Actual documentation is more lacking: I'm partway through a syntax man
page (including I think the most interesting parts of the language);
unfortunately, it's written in Global Script, and uses both features of
the language I haven't implemented yet and a library I haven't even
started.

> /me is curious.

I'm not sure what the best interface for publishing this is.  Blogs seem
to be somewhat standard; I should probably revive mine.

> And I'm wondering whether you're aware of the stuff Luke is working on
> (http://lukepalmer.wordpress.com/).

I've read all those posts through Planet Haskell; I don't think they've
made it into my list of interesting things to consider w.r.t. language
design yet.

> Personally, I've got some thoughts
> about a syntax, a preliminary parser and a lot of half-understood ideas.

Hmm.  Today's the first day I've really given serious consideration to
the viability of replacing Haskell with Global Script, even in
principle.  After all, trying to replace one of the most successful
research languages in existence would be hubristic.  (And as SPJ has
said, it won't happen by someone setting out to do it explicitly).  To
avoid hubris (which my study of Greek tragedy tells me is the greatest
danger to heroes), I've been busy convincing myself I'm really trying to
replace TeX, instead.  After all, TeX is clearly a much less adequate
programming language...

jcc


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


Re: [Haskell-cafe] Re: statep haskell-lang [was: Re: Hoogle and Network.Socket]

2009-02-26 Thread Jonathan Cast
On Thu, 2009-02-26 at 15:23 -0700, John A. De Goes wrote:
> On Feb 26, 2009, at 1:36 PM, Jonathan Cast wrote:
> > On Thu, 2009-02-26 at 13:25 -0700, John A. De Goes wrote:
> >> No, I hate C and will never use it again in my entire life unless
> >> forced to at the point of a gun.
> >
> > Why?  Its libraries are far better, its editors are far better [1],  
> > its
> > compilers are far better, its tool support is far better, it's
> > incomparably superior in every possible way to Haskell.
> 
> There are better languages than C with more libraries and better tools  
> (e.g. Java). I would chose one of those over Haskell for a commercial  
> product needing short time-to-market and a long shelf life.

OK, great.  But still: if you want Java, you know where to find it.

> Even  
> though Haskell is a superior language, there are other, often more  
> important considerations for anything but hobby coding.
> 
> > Except the relatively narrow criterion of the *language itself*.   
> > Maybe
> > making languages better is a worthwile pursuit, then?  Or do you still
> > think languages should be frozen in time[2] so the tools, compilers,
> > editors, libraries, etc. can undergo vast improvements?
> 
> I think to reap the benefits of a language, it must necessarily stop  
> evolving in ways that impose high costs on its user base.
> 
> > [2] For the record: I'd be content to see a frozen production  
> > language,
> > like Haskell, frozen in time; as long there's a credible other
> > evolveable language --- preferably one with zero backward- 
> > compatibility
> > requirements w.r.t. Haskell 98 or current or past GHC.
> 
> Let me ask you this question: If I wanted a language like Haskell, but  
> which is "Enterprise ready", where should I turn?

My *optimal* solution (not one I actually expect): Haskell forks.  One
frok retains backwards-compatibility, but gives up type families and any
new language developments.  If that language evolves, I can *guarantee*
you I will dislike any changes it makes (see Java generics for an
example; see the entirety of C++ for another).

The other fork continues to impose `high costs' on its user base, in the
name of being the best language it can possibly be.  This will
eventually involve just discarding features of Haskell 98 that get in
the way.

> My answer: Haskell. It's maturing and its slowed rate of evolution is  
> already having beneficial effects on other dimensions.

Beneficial as per you.  Not everyone agrees/cares --- not everyone is
doing Enterprise programming!

> >  Re-designing a
> > purely function research language from the ground up would be neat ---
> > but then it wouldn't be Haskell at all, and I wouldn't use Haskell,  
> > I'd
> > use the new language.  If I thought I could realistically leave the
> > Haskell community, I wouldn't be nearly so opposed to Haskell's
> > continued slide into practicality.
> 
> Why do you think you'll have no where else to go if Haskell continues  
> moving away from being a research language?

I have nowhere to go as yet.  (I am actually writing my own language;
when I get something usable for real work, I may very well just plain
un-subscribe from haskell-cafe, even though I will continue using
Haskell for bootstrapping for some time after that.)

> There are plenty of people  
> who would join you. I think you'd have far more company than you seem  
> to believe.

Yeah, I'd have the company of everyone who argues against you in this
(quite on-going) debate.  At least in spirit (how long it will take for
a new common research language to emerge from the mist is another
matter).

> And a fresh start, with absolutely zero requirements for  
> any backward compatibility, would open up many new directions.

I agree with that.  Although you're trying to argue those directions are
less valuable than I think they are!

In any case, I'm going to *try* not to continue this discussion any
further.  Best case nothing beneficial comes of it; worst case
participating in it slows down Global Script development.

jcc


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


Re: [Haskell-cafe] Coming up with a better API for Network.Socket.recv

2009-02-26 Thread Jonathan Cast
On Thu, 2009-02-26 at 22:45 +0100, Johan Tibell wrote:
> Hi all,
> 
> I find it quite inconvenient to use the `recv` function in
> Network.Socket as it throws an exception when reaching EOF and there's
> no way to check whether EOF has been reached before calling `recv`.
> This means that all calls to `recv` needs to be wrapped in an
> exception handler.

NB:

  tryJust (guard . isEOFError) $ recv ...

with base-4 or

  tryJust (ioErrors >=> guard . isEOFError) $ recv ...

with base-3, right?

> I've been thinking about changing the version of
> `recv` that's included in the network-bytestring library [1] so it
> behaves differently from the one in the network library. Before I do
> so I thought I should see if we can reach a consensus on what a nicer
> definition of `recv` would look like. My current thinking is that it
> would mimic what C/Python/Java does and return a zero length
> ByteString when EOF is reached.

+1

In the interest of totality.

Also, Prelude.getChar/System.IO.hGetChar should have return type

  IO (Maybe Char)

in the interest of totality.

> I'm also interested in understanding the reasons behind the design of
> the `recv` function in the network library. More generally, I'm
> interested in discussing the pros and cons of the current Haskell I/O
> library design where the different read functions throw EOF exceptions
> and you have to call e.g. hIsEOF before reading from a Handle.
> 
> 1. http://github.com/tibbe/network-bytestring

jcc


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


Re: [Haskell-cafe] Re: statep haskell-lang [was: Re: Hoogle and Network.Socket]

2009-02-26 Thread Jonathan Cast
On Thu, 2009-02-26 at 13:25 -0700, John A. De Goes wrote:
> No, I hate C and will never use it again in my entire life unless  
> forced to at the point of a gun.

Why?  Its libraries are far better, its editors are far better [1], its
compilers are far better, its tool support is far better, it's
incomparably superior in every possible way to Haskell.

Except the relatively narrow criterion of the *language itself*.  Maybe
making languages better is a worthwile pursuit, then?  Or do you still
think languages should be frozen in time[2] so the tools, compilers,
editors, libraries, etc. can undergo vast improvements?

jcc

[1] They're not; IDEs are for losers
[2] For the record: I'd be content to see a frozen production language,
like Haskell, frozen in time; as long there's a credible other
evolveable language --- preferably one with zero backward-compatibility
requirements w.r.t. Haskell 98 or current or past GHC.  Re-designing a
purely function research language from the ground up would be neat ---
but then it wouldn't be Haskell at all, and I wouldn't use Haskell, I'd
use the new language.  If I thought I could realistically leave the
Haskell community, I wouldn't be nearly so opposed to Haskell's
continued slide into practicality.


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


Re: [Haskell-cafe] Re: statep haskell-lang [was: Re: Hoogle and Network.Socket]

2009-02-26 Thread Jonathan Cast
On Thu, 2009-02-26 at 13:18 -0700, John A. De Goes wrote:
> Are you saying has been no progress since K&R C in the number of  
> libraries available to C programmers? And that C programmers still  
> have to edit files with vi and compile and link by specifying all  
> files on the command-line?
> 
> You may disagree, but the evidence points in the opposite direction.  
> There are tens of thousands of robust C libraries available to suit  
> any particular programming need. Many of Haskell's own libraries are  
> based on C versions. Tool support for the C language (not for some  
> successor you might think would exist if the language continued  
> evolving) can detect memory leaks, detect memory overwrites, apply  
> dozens of automatic refactorings to C large-scale C programs, etc.
> 
> Library and tool support for the C language is light years beyond  
> Haskell. It wouldn't be there if we had been through 20 iterations of  
> C each completely breaking backward compatibility.

Maybe you should use C then?

jcc


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


Re: [Haskell-cafe] Re: Hoogle and Network.Socket

2009-02-26 Thread Jonathan Cast
On Thu, 2009-02-26 at 06:30 -0700, John A. De Goes wrote:
> On Feb 25, 2009, at 7:49 PM, Achim Schneider wrote:
> > "John A. De Goes"  wrote:
> >
> >> The problem is that PL research is probably not going to stop
> >> evolving in our lifetimes. Yes, that research needs a venue, but why
> >> should it be Haskell? Haskell is a good language and it's time to
> >> start benefiting from the research that's already gone into it. That
> >> means some tradeoffs.
> >>
> > Why shouldn't it be Haskell?
> 
> More, why *can't* it be Haskell. Haskell is already constrained by  
> backwards compatibility, which limits future directions. Partial  
> functions and dependent typing do not seem to play well together, for  
> instance.
> 
> Moreover, look at the packages being uploaded to Hackage: they're  
> almost all trying to do useful stuff. The direction of Haskell has  
> already changed, and I don't see it reverting to its old course.
> 
> > Not really, look at e.g. type families, which give you much of the
> > power dependently typed languages give you while saying "nah, not yet"
> > to the question of how to deal with non-terminating typechecking.
> 
> *Some*, not *much*, and there are dependently typed languages that  
> have guaranteed terminating type checking.
> 
> > About the H' progress... It's hard to tell how many drops are needed  
> > to
> > make a bucket overflow, especially if you've got no idea what the
> > bucket looks like. What certainly isn't happening is people taking a
> > house, trying to overflow a badly leaking bucket.
> 
> As far as I know, H' was supposed to be completed many years ago.  
> Likely, it won't be completed for many more years. H2 is probably more  
> than a decade away, if it happens at all.

Here's to hoping it doesn't.  Practical languages, when they change,
*never* improve.  And that's going from study (although not experience!)
of 40 years of history.

jcc


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


Re: [Haskell-cafe] Re: Hoogle and Network.Socket

2009-02-26 Thread Jonathan Cast
On Thu, 2009-02-26 at 13:52 +0100, Daniel Fischer wrote:
> Am Donnerstag, 26. Februar 2009 13:41 schrieb John Lato:
> > I didn't phrase this well.  In the context of my argument, "design for
> > cross-platform" meant "avoid platform-limiting choices in the absence
> > of any compelling reasons otherwise", which really isn't the same.
> 
> 
> Could we sum that up as:
> 
> "Do not knowingly make your code unportable unless you have a good reason to"?
> 
> Are there any objections to that maxim?

Actually, yes.  But it's quite off-topic, not just as per thread but as
per mailing list.

jcc


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


Re: [Haskell-cafe] Re: Hoogle and Network.Socket

2009-02-25 Thread Jonathan Cast
On Wed, 2009-02-25 at 17:54 -0700, John A. De Goes wrote:
> It's a chicken-egg thing. A Linux or OS X developer tries Haskell and  
> finds he can write useful programs right away, with a minimum of fuss.  
> But a Windows user tries Haskell and finds he has access to very few  
> of the really good libraries, and even the cross-platform libraries  
> won't build without substantial effort. As a result, I bet it's easier  
> for a Linux or OS X developer to like Haskell than a Windows developer.
> 
> I use OS X exclusively myself, but I'll ensure my first published  
> Haskell library is cross-platform compatible, because I think it's  
> good for the community. The more people using Haskell, the more  
> libraries that will be written, the more bugs that will be fixed, the  
> more creativity that will be poured into development of libraries and  
> the language itself.

I don't think this is founded in experience.  The experience of the last
5 years is that the more people use Haskell, the more important
backward-compatibility concerns become, and the harder it becomes for
Haskell to continue evolving.

Creativity being poured into a language doesn't do much good if the
result is the language moving sideways, still less the language growing
sideways.

jcc


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


Re: [Haskell-cafe] forall & ST monad

2009-02-25 Thread Jonathan Cast
On Wed, 2009-02-25 at 10:18 -0800, Kim-Ee Yeoh wrote:
> 
> Heinrich Apfelmus wrote:
> > 
> > Now,
> > 
> >(forall a. T[a]) -> S
> > 
> > is clearly true while
> > 
> >exists a. (T[a] -> S)
> > 
> > should be nonsense: having one example of a marble that is either red or
> > blue does in no way imply that all of them are, at least constructively.
> >  (It is true classically, but I forgot the name of the corresponding
> > theorem.)
> > 
> 
> For the record, allow me to redress my earlier erroneous 
> assertion by furnishing the proof for the classical case:
> 
> (forall a. T(a)) -> S
> = not (forall a. T(a)) or S, by defn of implication

[For the record: this is the first point at which you confine yourself
to classical logic.]

> = not $ (forall a. T(a)) and (not S), by de Morgan's
> = not $ forall a. T(a) and (not S), product rule???

This step depends on the domain of quantification for the variable a
being non-empty; if the domain is empty, then the RHS is vacuously true,
while the LHS is equal to (not S).

> = exists a. not (T(a)) or S, de Morgan's again
> = exists a. T(a) -> S, by defn of implication

> The only wrinkle is obviously in the logical "and"
> of (not S) distributing under the universal quantifier.

jcc


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


Re: [Haskell-cafe] Re: Hoogle and Network.Socket

2009-02-25 Thread Jonathan Cast
On Wed, 2009-02-25 at 10:23 +, John Lato wrote:
> 4.  Cross-platform concerns are something that responsible developers
> need to consider, just like localization and i18n.  I.e., why
> *shouldn't* you think of that?

Sorry, wtf?  I have a *responsibility* to design software for a
miserably poorly-designed God-awful platform I'd have to pay *extra*
for, and even then couldn't get source to or *fix* if I found a bug?
No.  You don't control me, to the best of my knowledge you haven't done
squat for me, and by trying to force me to develop to *that* platform
you are actively attempting to harm me.

*plonk*

jcc


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


Re: [Haskell-cafe] Hoogle and Network.Socket

2009-02-21 Thread Jonathan Cast
On Sat, 2009-02-21 at 07:25 -0700, John A. De Goes wrote:
> I think the (valid) concern is that too many people are choosing  
> platform-specific packages when there are alternatives available  
> (albeit not as convenient in some cases), and this really hurts the  
> Windows community because Windows is so radically different from all  
> the other operating systems.
> 
> Not showing platform-specific packages by default *might* make package  
> writers more likely to develop cross-platform packages. We've heard  
> many times someone say, "I don't know if it works on Windows, never  
> really thought of that."

Um, why *should* I think of that?

jcc


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


Re: [Haskell-cafe] Hoogle and Network.Socket

2009-02-20 Thread Jonathan Cast
On Fri, 2009-02-20 at 09:17 +, Neil Mitchell wrote:
> Hi
> 
> > 1) Show all the functions (when the number is low), but place platform
> > specific functions under separate headers: "Windows",
> > "Linux/BSD/POSIX", "OS X", etc.
> 
> If a function isn't available on all OS's then all Hoogle would be
> encouraging you to do is break compatibility and stop me from using
> your software.

If my software works at all on Windows, it will only ever be by
accident; it certainly won't fit comfortably into the Windows
environment or look-and-feel.  If I'm writing a Unix text filter, why
should I give up a library or tool that would make my life easier
because it's only available on Unix?

jcc


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


Re: [Haskell-cafe] equational reasoning

2009-02-19 Thread Jonathan Cast
On Thu, 2009-02-19 at 23:06 +0200, Roman Cheplyaka wrote:
> * Wouter Swierstra  [2009-02-19 11:58:38+0100]
> > There are several problems with this approach.
> >
> > For example, I can show:
> >
> > const 0 (head []) = 0
> >
> > But if I pretend that I don't know that Haskell is lazy:
> >
> > const 0 (head []) = const 0 (error ) = error ...
> 
> Where does the last equality come from?

Pretending Haskell is strict.  It would be an axiom of Strict Haskell,
were someone to write such a thing, that

  forall a b (x :: String) (f :: a -> b). f (error x) = error x :: b

With the side condition that f is a lambda.

Then, we would know that, if f is a lambda of arity > 1 (or a constant
defined to be such a lambda), that (f a), where a is a value (such as
0), is equal to some lambda; so by congruence and the equation above, we
get (f a (error x) = error x) for all values a.

Which doesn't obviate the point that any proof-checker for *Haskell*
worth its salt would reject any alleged proof of (const 0 (error x) =
error x).

jcc


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


Re: [Haskell-cafe] what is [::]

2009-02-18 Thread Jonathan Cast
On Wed, 2009-02-18 at 16:28 +0100, Daniel van den Eijkel wrote:
> Dear Haskellers,
> 
> please can anybody tell me what [::] means or where to read about it?
> A 
> few days ago I saw this for the first time in my life, at the list of 
> instances of the Functor class, and I don't know where to look for 
> information. The search engines I tried didn't produce results for
> [::].

Try Googling `Haskell Parallel Arrays' instead.

jcc


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


Re: [Haskell-cafe] forall & ST monad

2009-02-16 Thread Jonathan Cast
On Mon, 2009-02-16 at 19:36 +0100, Wolfgang Jeltsch wrote:
> Am Montag, 16. Februar 2009 19:22 schrieb Wolfgang Jeltsch:
> > Am Montag, 16. Februar 2009 19:04 schrieb Kim-Ee Yeoh:
> > > Despite its rank-2 type, runST really doesn't have anything to do with
> > > existential quantification.
> >
> > First, I thought so too but I changed my mind. To my knowledge a type
> > (forall a. T[a]) -> T' is equivalent to the type exists a. (T[a] -> T').
> > It’s the same as in predicate logic – Curry-Howard in action.
> 
> Oops, this is probably not true. The statement holds for classical predicate 
> logic with only non-empty domains. But in constructivist logic only the first 
> of the above statements follows from the second, not the other way round.

Not only that, but giving runST an existential type would defeat its
safety properties.  Taking the `let open' syntax from `First-class
Modules for Haskell' [1], we can say

  let open runST' = runST in
  let
ref = runST' $ newSTRef 0
!() = runST' $ writeSTRef ref 1
!() = runST' $ writeSTRef ref 2
  in runST' $ readSTRef ref

This type-checks because the let open gives us the *same* skolemized
constant for s everywhere in the sequel.  Now, the above de-sugars to

  let open runST' = runST in
  let
ref = runST' $ newSTRef 0
x   = runST' $ writeSTRef ref 1
y   = runST' $ writeSTRef ref 2
  in case x of () -> case y of () -> runST' $ readSTRef ref

Haskell's semantics (if we could write runST in Haskell) would let us
re-order the cases in this instance --- with changes the over-all value
from 2 to 1.  In fact, if you inline x and y, you can discard the cases
entirely, so the expression has value 0.

Summary: Existential types are not enough for ST.  You need the rank 2
type, to guarantee that *each* application of runST may (potentially)
work with a different class of references.  (A different state thread).

jcc

[1] 
http://research.microsoft.com/en-us/um/people/simonpj/papers/first-class-modules/index.htm

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


Re: [Haskell-cafe] Re: Overloading functions based on arguments?

2009-02-13 Thread Jonathan Cast
On Fri, 2009-02-13 at 21:57 +0100, Daniel Fischer wrote:
> Am Freitag, 13. Februar 2009 21:08 schrieb Jonathan Cast:
> > On Fri, 2009-02-13 at 12:15 -0700, John A. De Goes wrote:
> > > On Feb 13, 2009, at 12:07 PM, Jonathan Cast wrote:
> > > > Exactly!  But if it fails, why on earth should any other use of map in
> > > > the module succeed?
> > >
> > > Because more information is known about other usages of map. Such is
> > > the nature of type inference.
> >
> > No it's not.  Type inference -- in Haskell --- means --- by definition!
> > --- looking up the principle type of each sub-term, specializing it
> > based on its use, and then generalizing to find the principle type of
> > the overall term.  Adding information can cause type inference to fail,
> > but --- in Haskell as it exists --- it cannot cause type inference to
> > succeed.
> 
> I'm not sure about the finer distinctions between type inference and type 
> checking as performed by Haskell implementations when compiling a module, but 
> what about polymorphic recursion, where adding information via a type 
> signature can be necessary to make the compilation succeed?

Um, sort of.  Adding --- or relaxing --- a type signature on a function
you *call* can make typing succeed when it would have failed.  But take
the recursion out of polymorphic recursion and it does become
problematic, yes.  For much the same reason the monomorphism restriction
is problematic, actually.

> Not what this thread is about, though.
> 
> >  Which is good!
> 
> Why is it good?

The compiler should fail when you tell it two mutually contradictory
things, and only when you tell it two mutually contradictory things.
Adding information cannot remove a contradiction from the information
set available to the compiler.  Therefore it should not stop the
compiler from failing.

And that is all I will say on this subject.

jcc


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


Re: [Haskell-cafe] Re: Overloading functions based on arguments?

2009-02-13 Thread Jonathan Cast
On Fri, 2009-02-13 at 12:15 -0700, John A. De Goes wrote:
> On Feb 13, 2009, at 12:07 PM, Jonathan Cast wrote:
> > Exactly!  But if it fails, why on earth should any other use of map in
> > the module succeed?

> Because more information is known about other usages of map. Such is  
> the nature of type inference.

No it's not.  Type inference -- in Haskell --- means --- by definition!
--- looking up the principle type of each sub-term, specializing it
based on its use, and then generalizing to find the principle type of
the overall term.  Adding information can cause type inference to fail,
but --- in Haskell as it exists --- it cannot cause type inference to
succeed.  Which is good!

jcc


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


Re: [Haskell-cafe] Re: Overloading functions based on arguments?

2009-02-13 Thread Jonathan Cast
On Fri, 2009-02-13 at 12:06 -0700, John A. De Goes wrote:
> On Feb 13, 2009, at 11:49 AM, Jonathan Cast wrote:
> > It breaks type inference.  I explained this at the time.  I can  
> > explain
> > it again:
> >
> >  import Data.List
> >  import Data.Set
> >  import Data.Map
> >
> >  warmFuzzyThingFirstOperation = map
> >
> > This gives an error currently.  Quite properly.  But if *any* use of
> > `map' type-checks, with those imports, why on earth should this one
> > fail?  You don't want to remove a wart from the language, you want to
> > introduce one!
> 
> Umm, no, that would still give an error. See definition of "one and  
> exactly one".

Exactly!  But if it fails, why on earth should any other use of map in
the module succeed?

jcc


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


Re: [Haskell-cafe] Re: Overloading functions based on arguments?

2009-02-13 Thread Jonathan Cast
On Fri, 2009-02-13 at 20:06 +0100, Daniel Fischer wrote:
> Am Freitag, 13. Februar 2009 19:49 schrieb Jonathan Cast:
> > On Fri, 2009-02-13 at 11:45 -0700, John A. De Goes wrote:
> > > On Feb 13, 2009, at 11:32 AM, Jonathan Cast wrote:
> > > > I believe the last time it was brought up, the proposal was that type
> > > > inference should fail on certain typeable terms.  That doesn't count.
> > >
> > > I'm referring to a rather conservative proposal wherein if there is
> > > one and exactly one definition that allows an expression to type, then
> > > name overloading in the same scope is permitted.
> > >
> > > Aside from exponential performance in pathological (but unlikely)
> > > cases, what issue do you have with such a proposal?
> >
> > It breaks type inference.  I explained this at the time.  I can explain
> > it again:
> >
> >   import Data.List
> >   import Data.Set
> >   import Data.Map
> >
> >   warmFuzzyThingFirstOperation = map
> 
> To do justice to the above proposal, in that situation more than one choice 
> would typecheck (were the other imports absent or qualified), so that should 
> also be rejected according to it.

Yeah, my objection is precisely that this trivial example is rejected.
If this use of map is rejected, then I claim *every* use of map should
be rejected.

jcc


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


Re: [Haskell-cafe] Re: Overloading functions based on arguments?

2009-02-13 Thread Jonathan Cast
On Fri, 2009-02-13 at 11:45 -0700, John A. De Goes wrote:
> On Feb 13, 2009, at 11:32 AM, Jonathan Cast wrote:
> > I believe the last time it was brought up, the proposal was that type
> > inference should fail on certain typeable terms.  That doesn't count.
> 
> 
> I'm referring to a rather conservative proposal wherein if there is  
> one and exactly one definition that allows an expression to type, then  
> name overloading in the same scope is permitted.
> 
> Aside from exponential performance in pathological (but unlikely)  
> cases, what issue do you have with such a proposal?

It breaks type inference.  I explained this at the time.  I can explain
it again:

  import Data.List
  import Data.Set
  import Data.Map

  warmFuzzyThingFirstOperation = map

This gives an error currently.  Quite properly.  But if *any* use of
`map' type-checks, with those imports, why on earth should this one
fail?  You don't want to remove a wart from the language, you want to
introduce one!

jcc


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


Re: [Haskell-cafe] Re: Overloading functions based on arguments?

2009-02-13 Thread Jonathan Cast
On Fri, 2009-02-13 at 11:29 -0700, John A. De Goes wrote:
> On Feb 13, 2009, at 11:23 AM, Jonathan Cast wrote:
> > Usually `when no ambiguity can arise', no?  Plenty of mathematical
> > practice rests on imprecision and the expectation that the human  
> > reader
> > will understand what you mean.  Haskell has to be understandable by  
> > the
> > machine (which is less forgiving, but also more reasonable!) as well.
> 
> Yes, and name overloading is decidable for machines as well, as the  
> feature exists in numerous languages,

Do those languages have full HDM type inference?  Do they have principle
types?  Are their principle types actually usable from the programmer's
perspective?  Those are the *bare minimum* requirements.

> and from time to time, we hear  
> talk of the feature for Haskell, as well.

I here jabbering all the time.  I try to tune most of it out.

> > Unless you, say, enjoy having type inference or something.
> 
> Name overloading and type inference are not incompatible -- the issue  
> has been discussed here before,

I believe the last time it was brought up, the proposal was that type
inference should fail on certain typeable terms.  That doesn't count.

jcc


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


Re: [Haskell-cafe] Re: Overloading functions based on arguments?

2009-02-13 Thread Jonathan Cast
On Fri, 2009-02-13 at 11:12 -0700, John A. De Goes wrote:
> I come from a mathematical background (in which it is quite common to  
> "overload" function names and operators in particular)

Usually `when no ambiguity can arise', no?  Plenty of mathematical
practice rests on imprecision and the expectation that the human reader
will understand what you mean.  Haskell has to be understandable by the
machine (which is less forgiving, but also more reasonable!) as well.

> , so from my  
> point of view, the lack of name overloading is a wart

What?  Are you sure of your lexical choice here?

>  on Haskell. That  
> such a feature would complicate type inference is more a concern to an  
> implementor, not to an end-user of Haskell like myself.

Unless you, say, enjoy having type inference or something.

jcc


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


Re: [Haskell-cafe] Re: Haddock Markup

2009-02-13 Thread Jonathan Cast
On Fri, 2009-02-13 at 11:08 +0100, Heinrich Apfelmus wrote:
> Jonathan Cast wrote:
> > 
> > NB: This example is *precisely* why I will never adopt MathML as an
> > authoring format.  Bowing and scraping at the alter of W3C is not worth
> > using such a terrible syntax, not ever.
> > 
> > (Indented, that's
> > 
> >   
> > 
> >   
> > x
> > 2
> >   
> >   +
> > 
> > 4
> > ⁢
> > x
> >   
> >   +  
> >   4
> > 
> >   
> > 
> > Which is still unforgivably horrible.  I *think* it's trying to say $x^2
> > + 4x + 4$, but I'm not confident even of that.
> 
> Yeah, MathML looks like a machine-only format to me, begging the
> question why they don't use a more compact format.
> 
> > I'm also unconvinced
> > it's actually easier to parse than $x^2 + 4x + 4$.)
> 
> While parsing is a solved problem in theory, a lot of people use some
> regular expression kludges or similar atrocities in practice.

Yeah, we even seem to have adopted one of their syntaxen [markdown].  

> Writing a
> proper parser is too complicated if your language doesn't have parser
> combinators. :)

Haddock, I believe, is written in a language that does.  If MathML
output is desired at some point (e.g., if browsers start doing better at
rendering it than at rendering images with TeX source-code alt-texts :)
the I think Haddock will still be capable of handling a reasonable input
language.

jcc


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


Re: [Haskell-cafe] Type families not as useful over functions

2009-02-12 Thread Jonathan Cast
On Fri, 2009-02-13 at 11:15 +1100, John Ky wrote:
> Hi Johnaton,
> 
> Ah yes.  That makes sense.  Is there a way to define type r to be all
> types except functions?

Not without overlapping instances.  I *think* if you turn on {-#
LANGUAGE OverlappingInstances #-} then

  instance Broadcast r where
type Result = [r]
broadcast xn = xn

should do what you want (instance resolution delayed until r has a type
constructor at top level; this instance selected if no other instance is
in scope --- should be equivalent to r not a function type unless
someone else defines an instance!); but I know that's not a pretty way
of doing things.

jcc


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


Re: [Haskell-cafe] Haddock Markup

2009-02-12 Thread Jonathan Cast
On Fri, 2009-02-13 at 13:30 +1300, Richard O'Keefe wrote:
> Let's take this example from the web.
>x2  +   
> 4⁢x  +  
> 4  

NB: This example is *precisely* why I will never adopt MathML as an
authoring format.  Bowing and scraping at the alter of W3C is not worth
using such a terrible syntax, not ever.

(Indented, that's

  

  
x
2
  
  +

4
⁢
x
  
  +  
  4

  

Which is still unforgivably horrible.  I *think* it's trying to say $x^2
+ 4x + 4$, but I'm not confident even of that.  I'm also unconvinced
it's actually easier to parse than $x^2 + 4x + 4$.)

jcc


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


Re: [Haskell-cafe] Another point-free question (>>=, join, ap)

2009-02-12 Thread Jonathan Cast
On Thu, 2009-02-12 at 23:36 +, Edsko de Vries wrote:
> Hi,
> 
> I can desugar
> 
>   do x' <- x
>  f x'
> 
> as
> 
>   x >>= \x -> f x'
> 
> which is clearly the same as
> 
>   x >>= f
> 
> However, now consider
> 
>   do x' <- x
>  y' <- y
>  f x' y'
> 
> desugared, this is
> 
>   x >>= \x -> y >>= \y' -> f x' y'
> 
> I can simplify the second half to
> 
>   x >>= \x -> y >>= f x'
>  
> but now we are stuck. I feel it should be possible to write something like
> 
>   x ... y ... f 
> 
> or perhaps
> 
>   f ... x ... y
> 
> the best I could come up with was
> 
>   join $ return f `ap` x `ap` y
> 
> which is not terrible but quite as easy as I feel this should be. Any hints?

Copying a bit of Applicative style, you could say

  join $ f `liftM` x `ap` y

I've thought it would be nice to have something like

  app :: Monad m => m (a -> m b) -> m a -> m b
  app af ax = join $ af `ap` ax

in the standard library.  Then you could simplify to

  f `liftM` x `app` y

I think that's as simple as you're going to get.  For more arguments,
say

  f `liftM` x `ap` y `app` z

The rule is: first application operator is `liftM` (or <$> --- I always
define Applicative instances for my monads); last application operator
is `app`; the operators in-between are all `ap`.  I think that's a
pretty straight-forward rule to follow.

jcc


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


Re: [Haskell-cafe] Type families not as useful over functions

2009-02-12 Thread Jonathan Cast
On Fri, 2009-02-13 at 10:34 +1100, John Ky wrote:
> Hi Haskell Cafe,
> 
> I tried using type families over functions, but when I try it
> complains that the two lines marked conflict with each other.
> 
> class Broadcast a where
>type Return a
>broadcast :: a -> Return a

> instance Broadcast [a -> r] where
>type Return [a -> r] = a -> [r] -- Conflict!
>broadcast fs a = []
> 
> instance Broadcast [a -> b -> r] where
>type Return [a -> b -> r] = a -> b -> [r] -- Conflict!
>broadcast fs a b = []
> 
> Given that in Haskell, every function of n+1 arguments is also a
> function of n arguments, this is likely the cause of the conflict.

This solution is somewhat in-extensible in the ultimate result type (r,
in your code); if the number of types r can take on is limited, it
should work well, though.  For expository purposes, I assume that r is
always Int:

  -- | Conal Elliot's semantic editor combinator argument
  argument :: (a -> a') -> (a -> b) -> (a' -> b)
  argument f g = g . f

  class Broadcast a where
type Return a
broadcast :: [a] -> Return a
  instance Broadcast Int where
type Return Int = [Int]
broadcast ns = ns
  instance Broadcast r => Broadcast (a -> r) where
type Return (a -> r) = a -> Return r
broadcast fs x = (map.argument) (const x) fs

jcc


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


Re: [Haskell-cafe] Is using Data.Dynamic considered a no-go?

2009-02-12 Thread Jonathan Cast
On Thu, 2009-02-12 at 19:04 +0100, Lennart Augustsson wrote:
> They are not unsafe in the way unsafePerformIO is,

I beg permission to demur:

  newtype Unsafe alpha = Unsafe { unUnsafe :: alpha }
  instance Typeable (Unsafe alpha) where
typeOf _ = typeOf ()

  pseudoSafeCoerce :: alpha -> Maybe beta
  pseudoSafeCoerce = fmap unUnsafe . cast . Unsafe

Note that

  pseudoSafeCoerce = Just . unsafeCoerce

> but I regard them
> as a last resort in certain situations.
> Still, in those situations they are very useful.

But I would agree with both of these.  As long as you *derive* Typeable.

jcc


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


Re: [Haskell-cafe] Re: Haskell tutorial for pseudo users?

2009-02-06 Thread Jonathan Cast
On Fri, 2009-02-06 at 14:56 +0100, Deniz Dogan wrote:
> 2009/2/6 Jonathan Cast :
> > Emacs' terminal is also lacking all the modern conveniences, like
> > addressable cursors and builtin line-editing designed for 1970s printing
> > terminals and practically no searching capabilities.  Alternatively, you
> > could say it's incompatible with modern Unix's biggest mistakes and
> > worst legacy issues.
> 
> With the risk of making this even more OT:
> 
> Emacs has three different types of shells built-in, at least to my
> knowledge. These are M-x shell, eshell and term. I'm not sure which
> one you are referring to as "Emacs' terminal", if any of them, but
> inf-haskell.el uses "shell" afaics.

I believe so.  But the colorization support in shell-mode is supplied by
comint; comint does fine with colorization normally, but I've had
problems with large files in the past.  (E.g., comint can't handle the
colorized output from a full run of the test suite at work).

> And what do you mean with "no
> searching capabilites?" What kind of searching are we talking here?

Emacs' incremental search (C-r, C-s).  Remember that my list is a
(sarcastic) list of advantages of M-x shell (and comint) over full-blown
Unix terminal emulators --- I had mis-remembered that Konsole and
GnomeTerm lacked builtin search capabilities.  (Checking, I see that
Konsole (KDE 3.5.10, which is what I have at work) does have poorish
search support.  But Emacs' search is still better!).

jcc


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


Re: [Haskell-cafe] Re: Haddock

2009-02-06 Thread Jonathan Cast
On Fri, 2009-02-06 at 09:40 +0100, David Waern wrote:
> 2009/2/6 Max Rabkin :
> > On Thu, Feb 5, 2009 at 4:25 PM, David Waern  wrote:
> >> As for running arbitrary commands, I think we are opening up to a lot
> >> of unfamiliar syntax. I'd like to hear what everyone thinks about
> >> that.
> >
> > I personally find it useful to have Haddock comments readable in the source.
> >
> > And aren't there security issues, too? So we'd have to have an option
> > to disable them, which would have to be on by default, and basically
> > they would be disabled by everybody but the writers of the comments
> > themselves.

> I think you can invoke any command using Setup.hs and Cabal already.

It's not a question of what's possible.  It's a question of how hard it
is to audit your code.  Do I just have to read your build system
(Setup.hs and its import tree, and maybe the Cabal file)?  Or do I have
to scan the source code for dubious constructs (unfortunately, we
already have this issue with Template Haskell)?  Most programs have
source code that is much larger than their build systems.

jcc


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


Re: [Haskell-cafe] Re: Haskell tutorial for pseudo users?

2009-02-05 Thread Jonathan Cast
On Fri, 2009-02-06 at 08:30 +0100, Achim Schneider wrote:
> Jonathan Cast  wrote:
> > On Mon, 2009-02-02 at 20:55 +, Andrew Coppin wrote:
> > > Deniz Dogan wrote:
> > > > Learn You a Haskell for Great Good (http://learnyouahaskell.com/)
> > > 
> > > Mmm, interesting.
> > > 
> > > Does anybody else think it would be neat if GHCi really did
> > > colourise your input like that?
> > 
> > Bleah.  More terminal hacking to break and/or slow Emacs to a crawl?
> > No thanks.
> > 
> A while ago, I'd say that emacs looks like a decent operating system,
> sadly lacking a decent editor.

I always wonder how many people who say that have actually *tried*
Emacs' editor.

> Now it seems that it's even lacking a
> decent terminal.

Actually, I think the issue is just that Emacs' ANSI color parsing code
is effectively O(n^2); when I really, really need colored output I run
the command in a separate window (with B&W output) and switch major
modes.

Emacs' terminal is also lacking all the modern conveniences, like
addressable cursors and builtin line-editing designed for 1970s printing
terminals and practically no searching capabilities.  Alternatively, you
could say it's incompatible with modern Unix's biggest mistakes and
worst legacy issues.

> I'm really not sure what to make of all that: Would
> you recommend using it?

Of course.  It sucks the least of any solution I've tried.  Barely.

> Eternal flamewars cast aside, what about integrating such a thing into
> yi? Yi has the advantage of working for both masochists _and_ efficient
> typists.

Yi has a terminal?  Maybe I should try it again.

jcc


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


Re: [Haskell-cafe] Haskell tutorial for pseudo users?

2009-02-05 Thread Jonathan Cast
On Mon, 2009-02-02 at 20:55 +, Andrew Coppin wrote:
> Deniz Dogan wrote:
> > Learn You a Haskell for Great Good (http://learnyouahaskell.com/)
> 
> Mmm, interesting.
> 
> Does anybody else think it would be neat if GHCi really did colourise 
> your input like that?

Bleah.  More terminal hacking to break and/or slow Emacs to a crawl?  No
thanks.

jcc


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


Re: [Haskell-cafe] Re: evaluation semantics of bind

2009-02-05 Thread Jonathan Cast
On Fri, 2009-02-06 at 00:51 +0100, Peter Verswyvelen wrote:
> On Thu, Feb 5, 2009 at 8:20 PM, ChrisK 
> wrote:
> Since this is strict there is no laziness and the code must
> evaluate the input and output "State RealWorld" to ensure they
> are not bottom or error.

> Interesting. I also thought it was the passing of the RealWorld that
> caused the sequencing, I never realized that the strictness played an
> important role here. 

> So what would happen if it would be lazy instead of strict? What kind
> of craziness would occur?

The order of side effects would be demand-driven, rather than
order-of-statement driven.  So if I said:

  do
 x <- getChar
 y <- getChar
 z <- getChar

then in the sequel, the first character I evaluated would be the first
character read.  Of course, Haskell's order of evaluation is undefined,
so whether the string read from STDIN was

   [x, y, z]
or [y, x, z]
or [z, x, y]

or some other permutation would be undefined.  And, of course, if I
never evaluated y at all, y would never be read --- there would be only
two characters of input.

Essentially, the program would act as if every statement was wrapped up
in an unsafeInterleaveIO.

jcc


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


Re: [Haskell-cafe] Monad explanation

2009-02-05 Thread Jonathan Cast
On Thu, 2009-02-05 at 15:52 -0800, David Leimbach wrote:
> 
> 
> On Thu, Feb 5, 2009 at 2:38 PM, Jonathan Cast
>  wrote:
> 
> On Thu, 2009-02-05 at 13:01 -0800, David Leimbach wrote:
> >
> >
> > On Thu, Feb 5, 2009 at 12:27 PM, Jonathan Cast
> >  wrote:
> >
> > On Thu, 2009-02-05 at 12:21 -0800, David Leimbach
> wrote:
> > >
> > >
> > > On Thu, Feb 5, 2009 at 11:25 AM, Andrew Wagner
> > >  wrote:
> > > I think the point of the
> Monad is
> > that it
> > > works as a container of
> stuff, that
> > still
> > > allows mathematically pure
> things to
> > happen,
> > > while possibly having some
> opaque
> > "other
> > > stuff" going on.
> >
> > >  This at least sounds, very wrong, even if
> it's not.
> > Monads
> > > are not impure. IO is, but it's only _one_
> instance
> > of Monad.
> > > All others, as far as I know, are pure.
> It's just
> > that the
> > > bind operation allows you to hide the
> stuff you
> > don't want to
> > > have to worry about, that should happen
> every time
> > you compose
> > > two monadic actions.
> 
> > > Well all I can tell you is that I can have (IO
> Int) in a
> > function as a
> > > return, and the function is not idempotent in
> terms of the
> > "stuff"
> > > inside IO being the same.
> >
> >
> > Sure it's the same.
> >
> > >  cmp /bin/cat /bin/cat
> > > cp /bin/cat ~
> > > cmp /bin/cat ~/cat
> > >
> >
> > Pretty much the same, anyway.
> 
> 
> > So if IO represents a program that when executed interacts
> with the
> > world's state, is it safe to say that when I return (State
> Int Int),
> > that I'm returning a "State program"?
> 
> 
> I won't object to it.  Othe people might, though.
> 
> > That'd make sense as it really does look like we force the
> State to be
> > evaluated with runState, evalState or execState.
> 
> > The only difference with IO then is that to get IO programs
> to run,
> > you have to do it inside another IO program.
> 
> 
> Meh.  Combining IO sub-programs into larger programs doesn't
> really `get
> them to run'.  Better to say that an IO value is meaningful
> only to the
> computer, and not mathematically (denotationally) useful.
> 
> All Haskell programs start as 

> main :: IO ()

> though... so they all get evaluated in the context of another IO ()
> don't they?

Well...  Haskell compilers and runhaskell-style interpreters (not
regular Hugs/ghci!) take the value of Main.main as `the program'.  But
that feels (to me --- I could be wrong) like an aspect of a particular
hosted environment.  REPLs can handle programs that aren't wrapped up in
IO at all; and there's no reason why IO has to be the type of
IO-performning-things in REPLs, either.  You could just as well write a
REPL that took, say, tangible values [http://haskell.org/haskellwiki/TV]
as input instead, and displayed them.  So it's more a matter of Haskell
implementations can be given an IO value to run than that combining IO
values together somehow runs them.

jcc


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


Re: [Haskell-cafe] Monad explanation

2009-02-05 Thread Jonathan Cast
On Thu, 2009-02-05 at 13:01 -0800, David Leimbach wrote:
> 
> 
> On Thu, Feb 5, 2009 at 12:27 PM, Jonathan Cast
>  wrote:
> 
> On Thu, 2009-02-05 at 12:21 -0800, David Leimbach wrote:
> >
> >
> > On Thu, Feb 5, 2009 at 11:25 AM, Andrew Wagner
> >  wrote:
> > I think the point of the Monad is
> that it
> > works as a container of stuff, that
> still
> > allows mathematically pure things to
> happen,
> > while possibly having some opaque
> "other
> > stuff" going on.
> 
> >  This at least sounds, very wrong, even if it's not.
> Monads
> > are not impure. IO is, but it's only _one_ instance
> of Monad.
> > All others, as far as I know, are pure. It's just
> that the
> > bind operation allows you to hide the stuff you
> don't want to
> > have to worry about, that should happen every time
> you compose
> > two monadic actions.

> > Well all I can tell you is that I can have (IO Int) in a
> function as a
> > return, and the function is not idempotent in terms of the
> "stuff"
> > inside IO being the same.
> 
> 
> Sure it's the same.
> 
> >  cmp /bin/cat /bin/cat
> > cp /bin/cat ~
> > cmp /bin/cat ~/cat
> >
> 
> Pretty much the same, anyway.

> So if IO represents a program that when executed interacts with the
> world's state, is it safe to say that when I return (State Int Int),
> that I'm returning a "State program"?

I won't object to it.  Othe people might, though.

> That'd make sense as it really does look like we force the State to be
> evaluated with runState, evalState or execState.

> The only difference with IO then is that to get IO programs to run,
> you have to do it inside another IO program.

Meh.  Combining IO sub-programs into larger programs doesn't really `get
them to run'.  Better to say that an IO value is meaningful only to the
computer, and not mathematically (denotationally) useful.

jcc



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


Re: [Haskell-cafe] Just how unsafe is unsafe

2009-02-05 Thread Jonathan Cast
On Thu, 2009-02-05 at 16:11 -0500, Andrew Wagner wrote:
> So we all know the age-old rule of thumb, that unsafeXXX is simply
> evil and anybody that uses it should be shot (except when it's ok). 

> I understand that unsafeXXX allows impurity, which defiles our ability
> to reason logically about haskell programs like we would like to.

Not just that!  Parametric polymorphism is unsound in combination with
mutable values; but unsafePerformIO turns on exactly that combination.

unsafeCoerce :: alpha -> beta
unsafeCoerce x = unsafePerformIO $ do
  let r = unsafePerformIO $ newIORef undefined
  r `writeIORef` x
  readIORef r

> My question is, to what extent is this true? 

unsafePerformIO is a true function --- in the absence of any fancy
compiler trickery --- on a small subset of its domain.  Outside of that
subset, I would regard use of unsafePerformIO simply as a bug ---
violation of an unchecked precondition.  Period.

> Suppose we had a module, UnsafeRandoms, which had a function that
> would allow you to generate a different random number every time you
> call it.

unsafePerformIO does not allow you to guarantee this!  If I defined

  myRandomNumber = unsafePerformIO $ randomNumber

then the compiler is permitted to call randomNumber (at most) *once*,
and use that number throughout the program.

> The semantics are relatively well-defined,

Leaving aside the issue above, I would think complete randomness was
nearly the worst possible case, semantically.  (The *worst* worst
possible case would be non-statistical non-determinism --- which is what
you actually get here).

> impurity is safely sectioned off in its own impure module, which is
> clearly labeled as such. How much damage does this do?

Well, it forces me to chase your libraries import lists to decide
whether I want to trust your code, for one thing.  Haskell is all about
making it easier to audit code, not harder.

> Can we push the lines elsewhere?

I'd rather not.

> Is sectioning unsafeXXX into Unsafe modules a useful idiom that we can
> use for other things as well?

I'd rather not write other unsafe functions at all.  Sectioning off
things that need to be unsafe into pure solutions --- like, say, monads
--- is a much better idea.  (Go read the global variables thread from
last year).

jcc


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


Re: [Haskell-cafe] Monad explanation

2009-02-05 Thread Jonathan Cast
On Thu, 2009-02-05 at 12:21 -0800, David Leimbach wrote:
> 
> 
> On Thu, Feb 5, 2009 at 11:25 AM, Andrew Wagner
>  wrote:
> I think the point of the Monad is that it
> works as a container of stuff, that still
> allows mathematically pure things to happen,
> while possibly having some opaque "other
> stuff" going on.

>  This at least sounds, very wrong, even if it's not. Monads
> are not impure. IO is, but it's only _one_ instance of Monad.
> All others, as far as I know, are pure. It's just that the
> bind operation allows you to hide the stuff you don't want to
> have to worry about, that should happen every time you compose
> two monadic actions.


> Well all I can tell you is that I can have (IO Int) in a function as a
> return, and the function is not idempotent in terms of the "stuff"
> inside IO being the same.

Sure it's the same.

>  cmp /bin/cat /bin/cat
> cp /bin/cat ~
> cmp /bin/cat ~/cat
>

Pretty much the same, anyway.

jcc


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


Re: [Haskell-cafe] Monad explanation

2009-02-05 Thread Jonathan Cast
On Thu, 2009-02-05 at 20:46 +0100, Lennart Augustsson wrote:
> You are absolutely right.  The statement
>   "The values of the IO monad are programs that do IO. "
> is somewhat nonsensical. Values don't do anything, they just are.

Technically, programs don't do anything either.  I think of values of
type IO a as being --- conceptually --- arbitrary sequences of machine
code instructions.  Just like a sequence of machine code instructions
can be stored away in /bin/cat, and not do anything, an IO value needn't
do anything, either.  Until it's stored in memory and the instruction
pointer set to its first instruction.  At which point, if you want to
get really picky, it's still the CPU doing things.  Which it is told to
do by its fixed microcode.  Which tells it to look at your program to
see what to do.  Which = looking at the `value' of your IO-typed
expression to see what to do.

jcc


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


Re: [Haskell-cafe] Bind as a sequencing operator (Was: evaluation semantics of bind)

2009-02-05 Thread Jonathan Cast
On Thu, 2009-02-05 at 11:47 -0700, m...@justinbogner.com wrote:
> Jake McArthur  writes:
> > m...@justinbogner.com wrote:
> > | Oops, sent this off list the first time, here it is again.
> > |
> > | Jake McArthur  writes:
> > |> m...@justinbogner.com wrote:
> > |> | Bind is a sequencing operator rather than an application operator.
> > |>
> > |> In my opinion, this is a common misconception. I think that bind would
> > |> be nicer if its arguments were reversed.
> > |
> > | If this is a misconception, why does thinking of it this way work so
> > | well? This idea is reinforced by the do notation syntactic sugar: bind
> > | can be represented by going into imperative land and "do"ing one thing
> > | before another.
> >
> > An imperative-looking notation does not make something imperative.
> >
> > Thinking of bind as sequencing really *doesn't* work very well. What
> > does bind have to do with sequencing at all in the list monad, for
> > example? What about the reader monad?
> >
> > - Jake
> 
> What doesn't bind have to do with sequencing in the list monad?
> Consider:
> 
>   [1..2] >>= return . (^2)
> 
> This says "generate the list [1..2] and then use it to generate a list
> of squares". It's more than just application, it's a description of a
> sequence of actions.

But not a temporal sequence.

(>>=) in IO is about temporal sequencing (modulo unsafeInterleaveIO,
forkIO, etc.)

> The whole point of list comprehensions (which is
> the only reason to have a list monad, as far as I know)

Huh?  I thought

newtype Parser s alpha = Parser {
  unParser :: StateT s [] alpha
  } deriving (Functor, Applicative, Alternative, Monad, MonadPlus)

was an entirely sufficient reason to have a list monad.

jcc


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


Re: [Haskell-cafe] about integer and float operations

2009-02-04 Thread Jonathan Cast
On Thu, 2009-02-05 at 01:10 +0100, Manlio Perillo wrote:
> Yitzchak Gale ha scritto:
> > In our case, the Python division first does a quick estimate
> > of the sizes of the two integers, and just returns zero if it
> > sees that there will be underflow on conversion to double.
> > So I made the following rough change to the Haskell:
> > 
> > -- An exact division
> > (/.) :: Integer -> Integer -> Double
> > x /. y
> > | y `div` x > 5*10^323 = 0
> > | otherwise= fromRational $ toRational x / toRational y
> > 
> 
> Right, but I would like to see a proper implemented function for exact 
> integer division in GHC.

(%) *is* a proper function for exact integer division.  But you'll find
plenty of Haskellers to balk at calling anything that returns a Double
`proper'.

jcc


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


Re: [Haskell-cafe] Monad explanation

2009-02-04 Thread Jonathan Cast
On Wed, 2009-02-04 at 23:55 +0200, Tymur Porkuian wrote:
> > Huh?  You can't actually over-ride function application --- Haskell's
> > built-in application always does exactly the same thing, at every type.

> It's a metaphor.

Oh, right.  That one word that means `inaccurate way of putting things'!
Invoking it solves everything!  I maintain that my claims were entirely
accurate.  I maintain your claims are in-accurate and confusing.

> In every case container has its own method of
> applying functions to its contents - e.g. instead of "f x" we write "x
> fmap f".

(NB. Typically only one of these will type-check; you know that, right?)

jcc


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


Re: [Haskell-cafe] Monad explanation

2009-02-04 Thread Jonathan Cast
On Wed, 2009-02-04 at 23:13 +0200, Tymur Porkuian wrote:
> Actually, I understand these types in terms of containers that
> override standard method of function application for their contents.

Huh?  You can't actually over-ride function application --- Haskell's
built-in application always does exactly the same thing, at every type.
You can, however, define new application-like operators that have other
application-like behaviors.  Haskell has a few of these:

* return
* (<$>)
* (<*>)
* (>>=) 

> In fact, there may be no contents, or several items, or nothing at
> all, or something strange, but the container behaves like there is a
> value of some type inside it.
> 
> In these terms:
> Maybe - container that may or may not contain something
> [a] - container that contains several values and applies function to all of 
> them
> State - container that has some other "secondary" value in it.
> IO - container that remembers passed functions and later will ask user
> for value, then apply functions to it.

Nice but irrelevant.  And I think your definition of IO is wrong.

> > * Monad: A monad M allows a function of n arguments (for n >= 0) to be
> > applied to n M values; in addition, if the function returns an M value
> > itself, you can combine that result with the arguments in a sensible
> > way.
> 
> Here, what does "sensible" mean?

Sensible.  As in, the definition of `join' in your monad can't be
senseless, or irrelevant to the monad's intended use.

> What do we override?

join

> Also, would it be right to say that Arrow is a container for functions
> that overrides function chaining?

No.

jcc


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


Re: [Haskell-cafe] Monad explanation

2009-02-04 Thread Jonathan Cast
On Wed, 2009-02-04 at 22:16 +0200, Tymur Porkuian wrote:
> For me, the key to understanding monads was that monad is "a value
> that know how to apply functions to itself". Or, more correctly, a
> container that knows how to apply functions to whatever is inside it.

Close.  (Monads are not `values' but types, but I'll let that slide).

Remembering that all Haskell functions take a single argument, but we
use currying to support an arbitrary number of arguments, we can arrange
the Monad type class hierarchy like this:

* Functor: A functor F allows a single function to be applied to a
single F value.  Multiple arguments (or none) are not supported; the
definition of application does what you probably *don't* want if the
function returns an F value itself.
* Applicative: An applicative functor A allows a function of n arguments
(for n >= 0) to be applied to n A values.  However, the definition of
application does what you probably *don't* want if the function returns
an A value itself.
* Monad: A monad M allows a function of n arguments (for n >= 0) to be
applied to n M values; in addition, if the function returns an M value
itself, you can combine that result with the arguments in a sensible
way.

jcc


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


  1   2   3   4   5   6   >