[EMAIL PROTECTED] wrote:
No. I mean by the "Haskell language" what is described in
the Haskell 98 Report. unsafePerformIO is not part of the language,
it is a value defined by one of the standard hierarchical libraries.
unsafePerformIO is part of the FFI addendum to the H98 report. So I
think
On Tue, Nov 23, 2004 at 08:50:45PM -0800, John Meacham wrote:
> Atom.hs from ginsu..
>
> This is perhaps the best example, and an incredibly useful piece of code
> for anyone struggling with space problems out there.
>
> it provides
>
> data Atom = ... (abstract)
>
> instance Ord Atom
>
On Tue, 23 Nov 2004 20:50:45 -0800, John Meacham <[EMAIL PROTECTED]> wrote:
> On Mon, Nov 22, 2004 at 05:03:30PM +0100, Benjamin Franksen wrote:
> > You have been asked more than once to present a *real-life* example to
> > illustrate that
> >
> > (a) global variables are necessary (and not just co
On Mon, Nov 22, 2004 at 05:03:30PM +0100, Benjamin Franksen wrote:
> You have been asked more than once to present a *real-life* example to
> illustrate that
>
> (a) global variables are necessary (and not just convenient),
> (b) both above mentioned alternatives are indeed unworkable.
First of
G'day all.
Quoting George Russell <[EMAIL PROTECTED]>:
> No. I mean by the "Haskell language" what is described in
> the Haskell 98 Report. unsafePerformIO is not part of the language,
> it is a value defined by one of the standard hierarchical libraries.
unsafePerformIO is part of the FFI ad
Marcin 'Qrczak' Kowalczyk wrote:
>What is
> exceptionToMaybe (f 0 + error "x")
>where
> f x = f x
>?
I guess that answers my question. :-)
-- Ben
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell
Ben Rudiak-Gould <[EMAIL PROTECTED]> writes:
> The intended semantics is
>
> / Nothing if x is a set of exceptions
> exceptionToMaybe x = | _|_ if x is _|_
> \ Just xotherwise
What is
exceptionToMaybe (f 0 + error "x")
where
John Goerzen wrote:
Python can work that way, but also adds another feature:
try:
blah
moreblah
finally:
foo
And in Haskell we have catch(Dyn), bracket, and finally. Are these not
enough?
I hadn't been aware of finally. That does seem to help.
One of the things I like about exceptions in
John Goerzen wrote:
>main = do
> xs <- return [ 1, 2, error "throw" ]
> `catch` \ any -> do
> putStrLn "caught"
> return [ 4, 5, 6 ]
> print xs
>
>When run, I get: Fail: throw
>
>In any case, in the more general case, I don't see a problem with that.
>I get a
John Goerzen wrote:
>On Tue, Nov 23, 2004 at 05:20:19PM +, Ben Rudiak-Gould wrote:
>
>>In any case, mapException is pure, and it's good enough for most of
the cases where one might want to catch exceptions outside the IO monad.
>
>Well, I'm maving trouble wrapping my head around how I could us
On 2004-11-23, Johannes Waldmann <[EMAIL PROTECTED]> wrote:
> in the following example, the handler won't catch the exception
> because of lazy evaluation. therefore, it's a different story
> than with exceptions in ML, Python, whatever strict language.
>
> main = do
> xs <- return [ 1, 2, err
On 2004-11-23, Benjamin Franksen <[EMAIL PROTECTED]> wrote:
> On Tuesday 23 November 2004 00:10, Aaron Denney wrote:
>> On 2004-11-22, Benjamin Franksen <[EMAIL PROTECTED]> wrote:
>> > On Monday 22 November 2004 09:38, Adrian Hey wrote:
>> >> You have yet to
>> >> explain how you propose to deal wi
On Tue, Nov 23, 2004 at 05:20:19PM +, Ben Rudiak-Gould wrote:
> >So what am I missing here?
>
> myfunc might raise more than one exception. For example,
>
>myfunc = error "x" + error "y"
Gotcha. That's the piece I was missing!
[ snip ]
>
> those I catch. If each particular implementa
On 23 Nov 2004, at 15:51, John Goerzen wrote:
On Tue, Nov 23, 2004 at 04:30:21PM +, Keean Schupke wrote:
I am sure this discussion has happened before, but I think for pure
functions, returning Either Error Result is the way to go.
That's certainly possible, but extremely tedious.
It sounds to
John Goerzen wrote:
>myfunc :: String -> Int
>
>This does some sort of string parsing and returns an Int. Or it may
>raise an exception if it couldn't parse the string. But it would do
>that every time.
>
>Now, let's say we have a non-IO catchJust. Of course, if we never need
>the value, we neve
I, too, had a gripe about this, and was pointed to an excellent paper that
explains all:
A Semantics for Imprecise Exceptions (1999)
Simon Peyton Jones, Alastair Reid, Tony Hoare, Simon Marlow, Fergus
Henderson
SIGPLAN Conference on Programming Language Design and Implementation
http://c
> And in Haskell we have catch(Dyn), bracket, and finally.
> > Are these not enough?
>
> We also have Control.Exception.try. :-)
>
> Peter
Yes. Control.Exception.try is defined in terms of Control.Exception.catch:
http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control.Exception
.
On Tue, Nov 23, 2004 at 03:43:09PM -, Bayley, Alistair wrote:
Thanks for your thoughtful reply. Let me try to expand on it a little
bit.
> Here's how I create "custom" exceptions; it doesn't seem onerous to me, but
> then I have a high tolerance for some kinds of coding pain:
>
> > data Sql
Bayley, Alistair writes:
> data SqliteException = SqliteException Int String
> deriving (Typeable)
> catchSqlite :: IO a -> (SqliteException -> IO a) -> IO a
> catchSqlite = catchDyn
> throwSqlite :: SqliteException -> a
> throwSqlite = throwDyn
I, too, think that's a good way to do it.
On Tue, Nov 23, 2004 at 04:30:21PM +, Keean Schupke wrote:
> I am sure this discussion has happened before, but I think for pure
> functions, returning Either Error Result is the way to go.
That's certainly possible, but extremely tedious.
One example: I've written an FTP client library. For
in the following example, the handler won't catch the exception
because of lazy evaluation. therefore, it's a different story
than with exceptions in ML, Python, whatever strict language.
main = do
xs <- return [ 1, 2, error "throw" ]
`catch` \ any -> do
putStrLn "caught"
> From: John Goerzen [mailto:[EMAIL PROTECTED]
>
> My other choice is to use Dynamic for my
> exceptions, but that makes it even more
> difficult to catch and handle
Here's how I create "custom" exceptions; it doesn't seem onerous to me, but
then I have a high tolerance for some kinds of coding
I am sure this discussion has happened before, but I think for pure
functions, returning Either Error Result is the way to go.
Keean.
John Goerzen wrote:
On Tue, Nov 23, 2004 at 04:12:52PM +0100, Johannes Waldmann wrote:
The other annoying thing is forcing it to run in the IO monad.
__
On Tue, Nov 23, 2004 at 04:12:52PM +0100, Johannes Waldmann wrote:
>
> >The other annoying thing is forcing it to run in the IO monad.
>
> necessarily so, since Haskell has non-strict semantics
> so it's not so clear when an exception is actually raised
> (you might have left the block that te
The other annoying thing is forcing it to run in the IO monad.
necessarily so, since Haskell has non-strict semantics
so it's not so clear when an exception is actually raised
(you might have left the block that textually contained the offending
expression , and the exception handler, a long t
On 23 Nov 2004, at 11:53, George Russell wrote:
I wrote (snipped):
> 3) It needs no extensions to the Haskell language, and only fairly
> standard hierarchical libraries like Data.IORef.
Lennart Augustsson wrote (snipped):
> It uses unsafePerformIO which is very much an extension to Haskell.
:)
B
Hi everyone,
I've been using Haskell for 1-2 months now, and feel fairly comfortable
with the language. However, my #1 gripe is the difficulty of working
with exceptions. I have two main complaints: difficulty of defining
custom exceptions, and difficulty of handling exceptions.
I've been worki
Can I suggest that this thread, interesting as it is, might usefully migrate to
haskell-café. (Apart from anything else, there's another similar thread
running there, and it makes sense to keep together.) Posting a summary back to
the Haskell list, in due course, would be great.
Simon
|
On Tuesday 23 November 2004 00:10, Aaron Denney wrote:
> On 2004-11-22, Benjamin Franksen <[EMAIL PROTECTED]> wrote:
> > On Monday 22 November 2004 09:38, Adrian Hey wrote:
> >> You have yet to
> >> explain how you propose to deal with stdout etc..
> >
> > I see absolutely no reason why stdxxx must
--
Apologies for multiple copies
--
CALL FOR PARTICIPATION
Seven
Call for Papers - ICTAC05
INTERNATIONAL COLLOQUIUM ON
THEORETICAL ASPECTS OF COMPUTING
Hanoi, Vietnam - 17--21 October, 2005
http://www.iist.unu.edu/ictac05
=
BACKGROUND AND OBJECTIVES
ICTAC is an International Colloquium on Theoretical Aspects of
Computing founded by the Inter
On 2004-11-22, Benjamin Franksen <[EMAIL PROTECTED]> wrote:
> On Monday 22 November 2004 09:38, Adrian Hey wrote:
>> You have yet to
>> explain how you propose to deal with stdout etc..
>
> I see absolutely no reason why stdxxx must or should be top-level mutable
> objects. They can and should be
Okay - but then you can keep state in haskell by using a driver thread
and channels like in the example I posted. I guess I should have said
it is best practice to check the real state rather than a (possibly wrong)
copy.
Keean.
Benjamin Franksen wrote:
On Tuesday 23 November 2004 10:39, Keean S
On Tuesday 23 November 2004 09:10, Adrian Hey wrote:
> On Monday 22 Nov 2004 6:27 pm, Lennart Augustsson wrote:
> > Personally, I can't believe I hear people arguing for global variables.
>
> Oh dear, here we go again. I repeat, AFAIK nobody who wants a solution to
> this problem is advocating the
On Tuesday 23 November 2004 10:39, Keean Schupke wrote:
> Adrian Hey wrote:
> >This is one situation, but certainly not the only possible one. You have
> >the same problem with interfacing to any unique stateful resource (or
> >even if you have a multiple but finite supply of these resources).
>
>
I wrote (snipped):
> 3) It needs no extensions to the Haskell language, and only fairly
> standard hierarchical libraries like Data.IORef.
Lennart Augustsson wrote (snipped):
> It uses unsafePerformIO which is very much an extension to Haskell. :)
Ben Rudiak-Gould wrote (snipped):
> I think by Hask
Lennart Augustsson wrote:
George Russell wrote:
(3) It needs no extensions to the Haskell language, and only fairly
standard hierarchical libraries like Data.IORef.
It uses unsafePerformIO which is very much an extension to Haskell. :)
I think by Haskell he means the common language currently imple
George Russell wrote:
(3) It needs no extensions to the Haskell language, and only fairly
standard hierarchical libraries like Data.IORef.
It uses unsafePerformIO which is very much an extension to Haskell. :)
-- Lennart
___
Haskell mailing list
[
Thanks to the encouraging post
http://www.haskell.org//pipermail/haskell/2004-November/014748.html
from Benjamin Franksen, I have implemented
my proposal which allows the user to define new global variables without
unsafePerformIO, NOINLINE and other such horrors.
http://www.haskell.org//pipe
Adrian Hey wrote:
I guess you mean the usual handle based approach, but this makes no
sense at all for a Haskell interface to some *unique* stateful resource
(eg. a piece of raw hardware or "badly designed" C library). The handle
is a completely redundant argument to all interface functions (there'
Adrian Hey wrote:
As for openDevice, if a device should only allow a single open I would
assume this is part of the device driver in the operating system?
(I know this is shifting blame. But I think it shifts it to where it
belongs. In the OS there will be an "open" flag per device.)
IOW there i
Is this a joke? Seriously if you writing the OS in haskell this is trivial,
you fork a thread using forkIO at system boot to maintain the driver,
all 'processes' communicate to the thread using channels, the thread
maintains local state (an IORef, or just a peramiter used recursively)
myDriver :
On Monday 22 Nov 2004 4:03 pm, Benjamin Franksen wrote:
> This is getting ridiculous. At least two workable alternatives have been
> presented:
>
> - C wrapper (especially if your library is doing FFI anyway)
> - OS named semaphores
Neither of these alternatives is a workable general solution.
The
> I don't know if HTk is still maintained.
Yes it is! It's time I put some more binary bundles up though.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell
On Monday 22 Nov 2004 11:26 am, Keean Schupke wrote:
> Adrian Hey wrote:
> >Just repeating this again and again doesn't make it any more true.
>
> Ditto... I for one think the best solution is to use the language as
> intended and pass the values as function arguments.
I guess you mean the usual h
On Monday 22 Nov 2004 6:27 pm, Lennart Augustsson wrote:
> Personally, I can't believe I hear people arguing for global variables.
Oh dear, here we go again. I repeat, AFAIK nobody who wants a solution to
this problem is advocating the use of "global variables", though it's
true that the proposal
46 matches
Mail list logo