eadIORef glob1
module Module2 where
glob2 :: IORef Int
glob2 <- mod1 >>= newIORef
mod2 :: IO Int
mod2 = readIORef glob2
Immediatly breaking my promise to shut up..
This is illegal because you're only allowed to use ACIO in top level <-
bindings and readIORef isn't (and cl
tal: 5
A few more:
wxHaskell 6
c2hs 1
GTK2HS1
SDL 0 !!
However, I happen to know that SDL suffers from the initialisation
issue and IIRC it needs at least 1 global to stop user using an unsafe
(possibly segfault inducing) cal
Adrian Hey wrote:
We have to have something concrete to discuss and this is the simplest.
Like I said there are a dozen or so other examples in the base package
last time I counted and plenty of people have found that other libs/ffi
bindings need them for safety reasons. Or at least they need
Ganesh Sittampalam wrote:
On Sun, 31 Aug 2008, Adrian Hey wrote:
Eh? Please illustrate your point with Data.Unique. What requirements
does it place on it's context? (whatever that might mean :-)
It requires that its context initialises it precisely once.
It's context being main?
Ganesh Sittampalam wrote:
On Sun, 31 Aug 2008, Adrian Hey wrote:
Thanks for taking the time to do this Dan. I think the safety
requirement has been met, but I think it fails on the improved API.
The main complaint would be what I see as loss of modularity, in that
somehow what should be a
bal variable" must be made so very painfully apparent in main
(and everywhere else on the dependency path too I guess).
In short, I just don't get it :-)
Purists aren't going to like it, but I think folk *will* be using "real"
global variables in I/O libs for the forseeab
Adrian Hey wrote:
"Global variables" are needed to ensure important safety properties,
but the only reasons I've seen people give for thread local variables
is that explicit state threading is just so tiresome and ugly. Well
that may be (wouldn't disagree), but I'm not
Ganesh Sittampalam wrote:
On Sat, 30 Aug 2008, Adrian Hey wrote:
Because if you could take a String and convert it to a Unique there
would be no guarantee that result was *unique*.
Well, yes, but if I implemented a library in standard Haskell it would
always be safely serialisable
aries!
So if this stuff matters someone had better figure it out :-)
It's a hack that isn't robust in many situations. We should find better
ways to do it, not standardise it.
Nobody's talking about standardising the current hack. This the whole
point of the top level <- prop
out in my last post, if this is a problem
with top level <- ACIO monad bindings it's still going to be
a problem (probably much worse) with unsafePerformIO hack IO
monad bindings.
This problem isn't just going to go away, no matter how lon
;re in the standard libraries!
So if this stuff matters someone had better figure it out :-)
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Brandon S. Allbery KF8NH wrote:
On 2008 Aug 29, at 4:22, Adrian Hey wrote:
Brandon S. Allbery KF8NH wrote:
On 2008 Aug 28, at 20:45, Adrian Hey wrote:
Lennart Augustsson wrote:
If Haskell had always taken the pragmatic path of adding what seems
easiest and most in line with imperative
Brandon S. Allbery KF8NH wrote:
On 2008 Aug 28, at 20:45, Adrian Hey wrote:
Lennart Augustsson wrote:
If Haskell had always taken the pragmatic path of adding what seems
easiest and most in line with imperative practice it would not be the
language it is today. It would be Perl, ML, or Java
with the right solution to a problem rather than picking some
easy way out.
BTW, unsafePerformIO seems quite pragmatic and easy to me, so let's
not get too snobby about this. (Sorry, I couldn't resist.)
Regards
--
Adrian Hey
___
Haskell-Ca
the world who can't write proper code, in Haskell or C
:-)
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Ganesh Sittampalam wrote:
On Thu, 28 Aug 2008, Adrian Hey wrote:
There's no semantic difficulty with the proposed language extension,
How does it behave in the presence of dynamic loading?
To answer this you need to be precise about the semantics of what
is being dynamically loaded
t's
needed to implement stdin the way you want to.
Can't recall expressing any opinion about how stdin should be
implemented so I don't know what your on about here.
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Ganesh Sittampalam wrote:
On Thu, 28 Aug 2008, Adrian Hey wrote:
implicit parameters (a highly dubious language feature IMO).
How can you say that with a straight face at the same time as advocating
global variables? :-)
Quite easily, what's the problem? IORefs, Chans etc are perf
rd libs, I have to ask why jump through all these
hoops? There's no semantic difficulty with the proposed language
extension, and it should be very simple to implement (John seems
to have done it already).
Regards
--
Adrian Hey
___
Haskell-Cafe mailing
Jonathan Cast wrote:
On Thu, 2008-08-28 at 10:00 +0100, Adrian Hey wrote:
Lennart Augustsson wrote:
> I don't don't think global variables should be banned, I just think
> they should be severly discouraged.
If you're saying a language should not provide a sound way to
Johannes Waldmann wrote:
Adrian Hey wrote:
There are plenty situations where it makes no semantic sense to allow
2 or more or some "thing". A list of all active processes for example.
"all" referring to what scope? perhaps there occurs a situation
with several pr
a possibility.
Now I could get the safety I need by wrapping all this stuff up in my
own custom augmented IO monad right at the start of main. But this
solution still lacks modularity. The top level <- bindings are just
a modular and extensible way to achieve the same thing AFAICS
(augmenting
Jonathan Cast wrote:
On Wed, 2008-08-27 at 11:53 +0100, Adrian Hey wrote:
John Meacham wrote:
As with all design decisions, it is sometimes the right thing and
sometimes the wrong one. And sometimes the most expedient. (which,
occasionally, is a perfectly valid driving force behind a certain
thing like that (AFAICS).
newAvailableDeviceHandles perhaps? I guess that could come in handy
if the user code decides it doesn't like the old ones for some
reason :-)
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
future even if they
don't right now, so you'd export getThing (= return thing) anyway,
rather then have an exported thing dissappear from the API at some
point.
My 2p..
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Ashley Yakeley wrote:
Adrian Hey wrote:
Maybe it would be safest to just say anything with a finaliser can't be
created at the top level.
Do you have an example of something that is correctly ACIO to create,
but has a problematic finaliser?
Sorry for the delay in getting my attention.
could live without them quite happily I guess :-)
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
could play that game with Data.Unique, for example.
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
ot at all convinced about the relevance.
It's a red herring IMO as you've introduced a very complex and
mysterious black box that itself cannot be implemented without making
use of "global variables". You can find them easily enough in the Linux
kernel source. I
all to do with interfacing with legacy code, it's a semantic
necessity and there's no legacy code involved.
If you want to dispute that then please show some real Haskell code that
does as good or better job without it (or point me too the relevant
legacy code that makes it necessary
base libs to eliminate the dozen or so uses of the "unsafePerformIO
hack" might be a good place to start. I'll even let you change the API
of these libs if you must, provided you can give a sensible explanation
why the revised API is better, safer, more convenient or whatever.
Regards
--
Adrian He
d
why does top level <- declarations take us away from it?
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
say anything with a finaliser can't be
created at the top level. We can always define an appropriate top level
"get" IO action using runOnce or whatever.
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
didn't feel right to me. But if you think about how finalisers
get run I'm inclined to think we should insist that they are ACIO too.
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
t source
documentation is needed too IMO).
I also think Neils idea of breaking darcs up from 1 monolithic prog
to a darcs lib suite is a good idea. This would give decent haddock
documentation for most of the code base and an easy way to have
multiple user interfaces (gui/web/command line based
collision cheap and if you
got the register allocation right (which is not hard on the ARM) you
could construct the overwhelming majority of heap records using a single
STMIA instruction. Almost seemed like it's instruction set was
designed for efficient FPL i
ath & writePath functions do involve a second traversal
but do not repeat all the comparisons. Also, provided not too much
has happened in between, they should be very fast as the nodes on
the path are probably still in cache. The important thing is that
in the case
ccing Haskell Cafe in case anyone else is interested in my answer..
Bryan O'Sullivan wrote:
Adrian Hey wrote:
I don't think anyone is interested in working on this or maintaining
it, so it's probably best not to use it for new stuff.
If nobody has stepped up yet, I'
use.
I don't think anyone is interested in working on this or maintaining
it, so it's probably best not to use it for new stuff.
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
s wasn't
good enough. I just chose algorithms empirically to minimise
comparison counts (not execution times), which is the right thing to
do for polymorphic implementations.
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Jan-Willem Maessen wrote:
On Apr 24, 2008, at 11:33 AM, Adrian Hey wrote:
Also, if you're likely to be using union/intersection a lot you should
know that Data.Map/Set are very slow for this because they use the
not efficient hedge algorithm :-)
OK, I'm going to bite here:
be Tries for non-trivial keys and (I
suspect) AVL trees of unboxed Ints for simple keys (serialisable
as 1 machine word). This is what that GSoC project is all about.
At the moment we have the exact opposite, Tries for Ints and balanced
trees for non-trivial ke
nd
it generates essentially pure H98 and there are ghc extensions we'd
probably want to use for performance reasons (like unboxed Ints and
unboxed tuples).
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
osals are good/ok/bad? Not me I assume :-)
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
d documented and someone
takes the trouble to finish it).
So maybe this is something for next years SOC?
That said, I know that type families are provisionally available, so
maybe doing something with generalised tries might be possible.
I don't min
about).
I think anyone wanting standard classes with different mathematical
properties should define them, stick them in Hackage and propose
them for Haskell-prime (if that's still happening?)
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
y.
If there's a need for a similar class where the (==) law doesn't
hold that's fine. But please don't insist that class must be Eq.
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
those primitives do too).
Just MO, the report doesn't make this clear 1 way or another AFAICS.
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Luke Palmer wrote:
On Thu, Mar 13, 2008 at 3:02 AM, Adrian Hey <[EMAIL PROTECTED]> wrote:
The report doesn't state that for all Ints, (x==y = True) implies that
x=y. There's no reason to suppose the Int instance is in any way
special, so do you really seriously consider the
it does apply. I think this is quite reasonable and I have
no intention of changing my programming habits to cope with weird
instances for which:
(x == y) = True does not imply x=y
or
max x y is not safely interchangeble with max y x.
I'm not saying some people are not right to want classes
Luke Palmer wrote:
On Thu, Mar 13, 2008 at 1:00 AM, Adrian Hey <[EMAIL PROTECTED]> wrote:
AFAICT the report is ambiguous about this, or at least the non-intutive
equality semantics are not at all clear to me from what I can see in
the Eq class definition (para 6.3.1). I think an the a
[EMAIL PROTECTED] wrote:
G'day all.
Adrian Hey wrote:
This might be a reasonable thing to say about *sortBy*, but not sort
as the ordering of equal elements should not be observable (for any
correct instance of Ord). It should be impossible to implement a
function which can discrim
Aaron Denney wrote:
On 2008-03-11, Adrian Hey <[EMAIL PROTECTED]> wrote:
Having tried this approach myself too (with the clone) I can confirm
that *this way lies madness*, so in future I will not be making
any effort to define or respect "sane", unambiguous and stable behaviour
ing example.
So is the correct conclusion from this that all (polymorphic) code
that assumes (x == y) = True implies x=y is inherently broken,
or is just this particular Eq instance that's broken?
Regards
--
Adrian Hey
___
Haskell-Cafe mailin
Jules Bean wrote:
Adrian Hey wrote:
This might be a reasonable thing to say about *sortBy*, but not sort
as the ordering of equal elements should not be observable (for any
correct instance of Ord). It should be impossible to implement a
function which can discriminate between [a,a],[a,b],[b,a
Ketil Malde wrote:
Adrian Hey <[EMAIL PROTECTED]> writes:
So really I think the docs have this backwards. It's sortBy that
implements a stable sort (assuming a suitably sane comparison function
I guess) and apparently sort is whatever you get from (sortBy compare).
But thi
Denis Bueno wrote:
On Tue, Mar 11, 2008 at 4:01 AM, Adrian Hey <[EMAIL PROTECTED]> wrote:
> and sorting is
> meant to be a permutation, so we happily have the situation where this
> has a correct answer: 2.
> Anything else is incorrect.
Isn't 3 also a permutati
ll be aiming for correctness and optimal efficiency on the
assumption that Eq and Ord instances are sensible.
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Jonathan Cast wrote:
On 10 Mar 2008, at 4:00 AM, Adrian Hey wrote:
Neil Mitchell wrote:
2) What does it do with duplicate elements in the list? I expect it
deletes
them. To avoid this, you'd need to use something like fromListWith,
keeping
track of how many duplicates there are
rd class method,
so that trie based sorts are possible (which should be faster for
complex data types). We should only use sort = sortBy compare as
the default.
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
should not be an instance
of Ord or Eq.
If this isn't the case then Foo should certainly not be an instance or
either class IMO.
If this was intended to be the case but in fact isn't the case, then
that's a bug.
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Denis Bueno wrote:
On Mon, Mar 10, 2008 at 10:10 AM, Adrian Hey <[EMAIL PROTECTED]> wrote:
>> The Eq instance you've given violates the law that (x == y) = True
>> implies x = y. Of course the Haskell standard doesn't specify this law,
>> but it shou
Ketil Malde wrote:
Adrian Hey <[EMAIL PROTECTED]> writes:
But seriously, once you admit the possibility that even if x == y it
still matters which of x or y is used in expressions than all hell
breaks loose. I shudder to think just how much Haskell code there must
be out there that is (a
or date
In such cases you should be using sortBy, not the overloaded sort
(you have several reasonable orderings for the same record type say).
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org
biasing" is
for all functions in the API. Furthermore, until quite recently some
function implementations in Data.Map we're actually broken wrt the
stated "biasing" policy (though few actually noticed this for obvious
reasons). Perhaps some still are? Who knows..
Regards
--
Adria
acefully, that is
keeping a count won't cut it, because of sortBy.
For the overloaded sort, I would say keep a count of duplicates is
a perfectly reasonable and correct solution (and more space efficient
too). For sortBy things need specifying more precisely as it can accept
any old
this is the case then
the issue you raise wrt sort behaviour is irrelevant.
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Adrian Hey wrote:
or specify and control the behaviour of their behaviour for such
instances.
Urk, sorry for the gibberish. I guess I should get into the habit of
reading what I write before posting :-)
Regards
--
Adrian Hey
___
Haskell-Cafe
ey should. Otherwise knowing a
type is an instance of Ord tells me nothing that I can rely on.
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
rly" penalised this way, but I'm reminded of this post
from John Meacham..
http://haskell.org/pipermail/glasgow-haskell-users/2007-May/012470.html
The other big problem with stackgobbler in practice is the risk of
stack overflow. For p=15 it would not work at all for ghc default
stack limit.
Philip Armstrong wrote:
On Mon, Feb 18, 2008 at 05:56:41PM +, Adrian Hey wrote:
Philip Armstrong wrote:
On Sun, Feb 17, 2008 at 10:01:14PM +, Adrian Hey wrote:
BTW, I find this especially ironic as fromDistinctAscList is the
perfect
example what I was talking about in another thread
limit does provide users with some
protection against this. But IMO the bug is in the ghc rts, not the
users source code most of the time :-(
I think at the minimum, the stack shrinking mod you suggested should
be implemented before the limit is removed.
Regards
--
Adrian Hey
Philip Armstrong wrote:
On Sun, Feb 17, 2008 at 10:01:14PM +, Adrian Hey wrote:
BTW, I find this especially ironic as fromDistinctAscList is the perfect
example what I was talking about in another thread (continuation passing
madness caused by an irrational fear of stack use).
In *some
never be needed).
So I still think the stack management system should be designed so
that as far as is practical (given finite memory), any expression
that can be built on the heap can also be evaluated without causing
a "stack overflow".
But I gue
use of fromDistinctAscList.
BTW, I find this especially ironic as fromDistinctAscList is the perfect
example what I was talking about in another thread (continuation passing
madness caused by an irrational fear of stack use).
As to what's really going on here, I haven't figured it
Adrian Hey wrote:
AFAICT neilGobbler isn't even entirely safe as an implementation of
an eager take. There's nothing the Haskell standard to stop it being
transformed into..
neilGobbler :: Int -> [x] -> [x]
neilGobbler n xs = length (take n xs) `seq` take n xs
Whoops, I see
d into..
neilGobbler :: Int -> [x] -> [x]
neilGobbler n xs = length (take n xs) `seq` take n xs
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
east twice as much heap as stackGobbler,
which would be the implementation of choice for both simplicity and
performance if it wasn't for this stack management problem.
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
debate despite it being obvious to any thinking person that I was
correct. Denial of the reality of some very simple examples of the
problem was typical of that debate too.
:-)
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
wing them to grow at all. Why not just limit them to 4K?
Actually I think the latter option above might be good way to discover
how many "bug" free Haskell progs there really are out there. Precious
few I suspect :-(
Regards
--
Adrian Hey
__
Luke Palmer wrote:
On Feb 5, 2008 2:50 AM, Adrian Hey <[EMAIL PROTECTED]> wrote:
I think it bites a lot less often than it otherwise would because most
people will deliberately chose to use heap in preference to stack (at
least when writing "eager" code) just to avoid the probl
ack" at all. But I guess we'd
be talking about a complete re-write of the pretty much all the
rts and much of the compiler to do this :-(
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Stefan O'Rear wrote:
On Mon, Feb 04, 2008 at 10:13:12PM +0000, Adrian Hey wrote:
Also
remember that this behaviour never wastes more than 50% of the stack,
which is a relatively small amount.
Only if the stack is relatively small. Would you say the same about
heap, or about a stack that
s just because it happens
to cause a "stack overflow" with ghc. You might reasonably argue that
it has a bug if it uses a lot of memory with any plausible Haskell
implementation (one way or another) *and* you can show that there is
an alter
askell-users/2007-May/012472.html
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
investigating a programs stack use there must be
a better way of doing it than deliberately inducing a crash in any
program that exceeds 8M of stack.
Thanks for the answer though. I think I'll write a ticket about this :-)
Regards
--
Adrian Hey
___
recursive and explicitly
implements the stack as a reversed list accumulator, which then
has to be reversed at the end, so will burn twice as much heap
to get a result as stackGobbler (at least if we already know the
list has evaluated at least up to the point where it's tail get
choppe
implementation, so it
really should be ghc that fixes the problem, or at least admits
responsibility :-)
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
oo fast if folk were
silly enough to make use of the stack.
So perhaps the current ghc defaults are too generous. What limit do you
think should be placed on the stack size that a non buggy program can
use?
Regards
--
Adrian Hey
___
Haskell-Cafe maili
are a pretty common cause of program failure
IME, not at all rare. At least, far more common than whatever error
message you get from heap exhaustion (can't even remember the last
time I saw one of those).
Regards
--
Adrian Hey
___
Haskell-Cafe m
ne think of an easy workaround?
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
s 1.8, unless you want a
pre-compiled windows version in which case you're stuck with 1.3 :-)
Anyone know what's going on?
Thanks
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
regularly whined about of all the "standard" libs.)
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
cause it's just doing more work!) then I'd love
to see a test case.
I wonder if this could be related to what I observed with AVL trees and
mentioned a while back (using a strict data type is slower than using
explicit seqs to get the same strictness).
R
Hello Folks,
Adrian Hey wrote:
If anyone is interested in the job then I
suggest they contact myself or Jean-Philippe Bernardy.
Sigh..no sooner than I go and write something like that than the IEE (or
I should say IET) go and break my mail alias. So sorry if anyone did
actually try to contact
over these libs may feel they need from me. I might even contribute a
few patches from time to time myself :-)
Thanks
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
Bulat Ziganshin wrote:
because program that require 8mb stack, will probably require 8gb when
processing more data :)
So.. what? You could say the same about heap, which was rather the point
of the earlier thread.
Regards
--
Adrian Hey
___
Haskell
tp://www.haskell.org/pipermail/glasgow-haskell-users/2007-May/012467.html
Regards
--
Adrian Hey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
as viable, but during
a long and heated flame war on the Clean mailing list it became clear
that the Clean team did not agree with my point of view, so things
were not likely to change any time soon :-(
Regards
--
Adrian Hey
___
Has
Chaddaï Fouché wrote:
2007/9/26, Adrian Hey <[EMAIL PROTECTED]>:
Chaddaï Fouché wrote:
There can't be alternatives, unsafeIO throw by the window most
guarantee that Haskell can give you and you have to provide them
yourself (with a proof of this part of your program), but it's
1 - 100 of 207 matches
Mail list logo