Hi all,
I've been playing a bit with gadts and existentials lately, and I
have an example where I don't quite understand the behavior of
ghc. The expression in question typechecks sometimes in some
versions of ghc, depending on where you write it, and not in
other versions. Some other people I'v
On 5 Feb 2008, at 10:14 PM, Jeff φ wrote:
On Feb 5, 2008 4:58 PM, Chaddaï Fouché <[EMAIL PROTECTED]>
wrote:
2008/2/5, Jeff φ <[EMAIL PROTECTED]>:
> This is interesting. I've been programming in Concurrent Clean
for a while.
> Instead of monads, Clean supports unique types for mutable
I forgot to attach the source code for ArrayTest.icl
ArrayTest.icl
Description: Binary data
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe
On Feb 5, 2008 4:58 PM, Chaddaï Fouché <[EMAIL PROTECTED]> wrote:
> 2008/2/5, Jeff φ <[EMAIL PROTECTED]>:
> > This is interesting. I've been programming in Concurrent Clean for a
> while.
> > Instead of monads, Clean supports unique types for mutable arrays and
> IO.
> > In Clean, I can write co
On Feb 5, 2008 9:44 PM, Uwe Hollerbach <[EMAIL PROTECTED]> wrote:
> lisp> (UTCtime)
> "Wed Feb 6 03:57:45 UTC 2008"
> ---
> lisp> (UTCtime 1.203e9)
> "Thu Feb 14 14:40:00 UTC 2008"
> --
> But after that, it sure seems to me as if I've taken data out of the
> IO monad... haven't I? Given th
I'm having a little difficulty finding full properties for Parsec3's
Stream class, largely because I don't want to overspecify it with regard
to side-effects. Here's the class:
> class Stream s m t | s -> t where
>uncons :: s -> m (Maybe (t,s))
The idea is that:
* unfoldM uncons gives th
Hello, haskellers, I have a question for you about the IO monad. On
one level, I seem to be "getting" it, at least I seem to be writing
code that does what I want, but on another level I am almost certainly
not at all clear on some concepts. In various tutorials around the
web, I keep finding this
> > > I'm almost done with the decimal library but it would be nice to check
> > > some Integer implementations for future inclusion. So, Aaron, Björn,
> > > are your implementations available somewhere?
> >
> > As noted elsewhere in the thread my implementation is available at:
> >
> > http://www.
On Wed, Feb 6, 2008 at 11:43 AM, Stuart Cook <[EMAIL PROTECTED]> wrote:
> My development version has removed the need for
> Control.Monad.Exception and Control.Arrow. The only remaining H98
> incompatibility I can think of is the use of foldl' in fromList.
Version 0.2.1 features:
* almost-H9
Hmm. It looks like I forgot a step, and it probably would segfault as
given. That's what I get for mucking about with unsafe* functions.
How about this?
let frozen_ary = unsafeFreeze myArray
let ary_max = foldl1' max $ elems frozen_ary
in ary_max `seq` map (1/ary_max) $ unsafeThaw frozen_ary
Th
On Tue, Feb 05, 2008 at 06:00:38PM -0600, John Lato wrote:
> -- let ary_max = foldl1' max $ elems $ unsafeFreeze myArray
>
> If you use a boxed array type (IOArray or STArray) for myArray, and
> compiled with GHC, no copying is necessary (you may need to use type
> annotations to guarantee this).
Am 05.02.2008 um 21:27 schrieb Dan Weston:
Matthew,
Your SuperMonad seems remarkably similar to Gabor Greif's Thrist
datatype [1,2] reported only six days ago on this list [3].
Can you compare/contrast your class approach with his polymorphic
type approach? Or have I completely confused
On Tue, Feb 5, 2008 at 11:33 PM, Christian Maeder
<[EMAIL PROTECTED]> wrote:
> Neil Mitchell wrote:
> > Yes, an MTL dependency is nothing to worry about at all, and isn't
> > worth even thinking about removing given its actually used.
>
> I would appreciate haskell98 portability!
My development
At least for file processing, I don't think the lazy solution is as
bad as some people on this list indicate. My solution was to define a
function processAudioFile :: (Handle, Handle) -> (ASig -> ASig) -> IO
(), similar to interact. The function reads from the first handle and
writes to the secon
Hello Adrian,
Tuesday, February 5, 2008, 10:15:59 PM, you wrote:
>> i would be also happy if ghc will return unused *heap* memory back to
>> OS - it's immediately required for my GUI program where users may open
>> huge files and then close them. but i personally don't have the same
>> need for *
On Feb 5, 2008 6:06 PM, Dan Weston <[EMAIL PROTECTED]> wrote:
> Can you do this with a GHC rule? Something like:
>
> {-# RULES
>"join_dot_fmap_return/id" forall x . join (fmap return x) = x
> #-}
>
> Dan
I guess this would make use of the rule (otherwise the transformation
would change th
Matthew,
Your SuperMonad seems remarkably similar to Gabor Greif's Thrist
datatype [1,2] reported only six days ago on this list [3].
Can you compare/contrast your class approach with his polymorphic type
approach? Or have I completely confused the two because of the similar
kind of their ar
Jefferson Heard wrote:
> I thought this was fairly straightforward, but where the marked line
> finishes in 0.31 seconds on my machine, the actual transpose takes
> more than 5 minutes. I know it must be possible to read data in
> haskell faster than this.
I took a look into this, writing a simil
Can you do this with a GHC rule? Something like:
{-# RULES
"join_dot_fmap_return/id" forall x . join (fmap return x) = x
#-}
Dan
Henning Thielemann wrote:
On Tue, 5 Feb 2008, Brandon S. Allbery KF8NH wrote:
On Feb 5, 2008, at 8:31 , Henning Thielemann wrote:
How do you convince the
On Feb 5, 2008 8:29 PM, Bjorn Buckwalter <[EMAIL PROTECTED]> wrote:
>
> On Feb 5, 2008 2:16 PM, Alfonso Acosta <[EMAIL PROTECTED]> wrote:
> > On Feb 5, 2008 4:10 PM, Henning Thielemann
> > <[EMAIL PROTECTED]> wrote:
> > >
> > > On Fri, 1 Feb 2008, Aaron Denney wrote:
> > >
> > > > On 2008-02-01, Bj
On Feb 5, 2008 2:16 PM, Alfonso Acosta <[EMAIL PROTECTED]> wrote:
> On Feb 5, 2008 4:10 PM, Henning Thielemann
> <[EMAIL PROTECTED]> wrote:
> >
> > On Fri, 1 Feb 2008, Aaron Denney wrote:
> >
> > > On 2008-02-01, Bjorn Buckwalter <[EMAIL PROTECTED]> wrote:
> > > > If Naturals had been sufficient fo
On Feb 5, 2008 4:10 PM, Henning Thielemann
<[EMAIL PROTECTED]> wrote:
>
> On Fri, 1 Feb 2008, Aaron Denney wrote:
>
> > On 2008-02-01, Bjorn Buckwalter <[EMAIL PROTECTED]> wrote:
> > > If Naturals had been sufficient for me I wouldn't have done my own
> > > implementation (I'm unaware of any other
Bulat Ziganshin wrote:
Hello Matthew,
Monday, February 4, 2008, 11:45:51 PM, you wrote:
That would be nice. But its only beneficial if there are programs
which takes large amounts of stack at some point, but then shrink down
to very little stack and continue for a reasonable amount of time.
Hi Ian,
Should gmp-devel be an archive (.a) or a shared object (.so)? If an .a,
don't I have to have an environemmt var to point at it's directory?
I tried your sequence below on unix-2.2.0.0 and still cannot resolve "gmp".
I did find one gmp .rpm on one of the RHEL cds but without "-devel".
Hi
> If you mean an example of coding style and choice of stack vs. heap,
> I already have..
>
> http://www.haskell.org/pipermail/haskell-cafe/2008-January/038832.html
I'm at a loss as why you want a strict version of take. It's clearly
not for performance, as it performs slower. I'd say both t
On Feb 5, 2008 6:50 PM, Adrian Hey <[EMAIL PROTECTED]> wrote:
>
> 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 (
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 problem. But it still
b
I've switched to this, which gets rid of the ByteString instances
fairly quickly. None of them make it into the final map. I'm still
not getting any faster response out of it, and it also complains that
my stack size is too small for anything about 128K records or more.
import qualified Data.Byt
If the strings are relatively short, there can be a bottleneck
in the current Ord instance for Bytestrings. When lots of them
are in a map, the ffi calls to memcmp dominate.
I've a fix for this (do it all in Haskell for small strings), and
can push it if someone complains some more.
jefferson.r
I thought this was fairly straightforward, but where the marked line
finishes in 0.31 seconds on my machine, the actual transpose takes
more than 5 minutes. I know it must be possible to read data in
haskell faster than this. I'm trying to read a 100MB comma delimited
file. I've tried both CSV m
Hello Jeff,
Tuesday, February 5, 2008, 7:36:27 PM, you wrote:
> Changing the subject slightly, I once wrote code in Concurrent
> Clean that filtered a file that was larger than the available memory
> on my PC.
> Is this possible with Monads in Haskell?
google for "simple unix tools"
--
Best
Hello Henning,
Tuesday, February 5, 2008, 6:01:27 PM, you wrote:
> Is Haskell's type system including extensions strong enough for describing
> a function, that does not always return a trivial value? E.g.
>(filter (\x -> x==1 && x==2))
such things may be detected by (too) smart compiler, bu
On Feb 5, 2008 4:36 PM, Jeff φ <[EMAIL PROTECTED]> wrote:
>
> I want to say thanks to everyone who responded to my mutable array post.
> I'm going to work through and experiment with all the comments people
> posted. It might take me a while.
>
> Luke Palmer wrote:
> > Hmm, how big is the array?
Jeff φ wrote:
> Changing the subject slightly, I once wrote code in Concurrent Clean that
> filtered a file that was larger than the available memory on my PC. I did
> this by creating a function that returned the contents of the original file
> as a lazy list.
Doing this is idiomatic in Haskell,
I want to say thanks to everyone who responded to my mutable array post.
I'm going to work through and experiment with all the comments people
posted. It might take me a while.
Luke Palmer wrote:
>
> Hmm, how big is the array? If it's pretty big, that's
> understandable. Frankly, it's becaus
[CC'ed to the agda mailing list as well]
On Feb05, Henning Thielemann wrote:
>
> Is Haskell's type system including extensions strong enough for describing
> a function, that does not always return a trivial value? E.g.
>(filter (\x -> x==1 && x==2))
> will always compute an empty list. Usi
On Feb 5, 2008 7:48 AM, Matthew Sackman <[EMAIL PROTECTED]> wrote:
> So I was thinking how dull and uninspiring the current definiton of
> Monad really is and came up with some more interesting
> parameterisations. The only problem with this one is I'm a) not sure if
> it still is a Monad and b) ve
On Fri, 1 Feb 2008, Aaron Denney wrote:
> On 2008-02-01, Bjorn Buckwalter <[EMAIL PROTECTED]> wrote:
> > If Naturals had been sufficient for me I wouldn't have done my own
> > implementation (I'm unaware of any other implementation of Integers).
> > And there is certainly a lot of value to the cl
(Sorry for the late reply.)
[EMAIL PROTECTED] wrote:
I'd really like to write
class (forall a . Ord p a) => OrdPolicy p where
but I guess that's (currently) not possible.
Actually, it seems that something like this can be achieved, at some price.
First, I change the statement ;-) to
cl
Is Haskell's type system including extensions strong enough for describing
a function, that does not always return a trivial value? E.g.
(filter (\x -> x==1 && x==2))
will always compute an empty list. Using an appropriate signature for
the function it shall be rejected at compile time, becau
So I was thinking how dull and uninspiring the current definiton of
Monad really is and came up with some more interesting
parameterisations. The only problem with this one is I'm a) not sure if
it still is a Monad and b) very unsure if it's of any use. There's the
possibility that chucking Cont in
On Tue, 5 Feb 2008, Cale Gibbard wrote:
> Are many people using mapAccumR? How much would it hurt to change it?
I cannot remember having ever used mapAccumR, but I used mapAccumL where I
used mapM on State monad before, in order to avoid dependency on MTL (and
thus non-Haskell-98 features).
On Tue, 5 Feb 2008, Brandon S. Allbery KF8NH wrote:
> On Feb 5, 2008, at 8:31 , Henning Thielemann wrote:
>
> > How do you convince the compiler that
> > 'join (fmap return x) == x' ?
>
> How do you convince it that the current formulation of Monad obeys
> the monad laws? (rhetorical)
My poin
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 problem. But it still
> bites pretty of
On Feb 5, 2008, at 8:31 , Henning Thielemann wrote:
How do you convince the compiler that
'join (fmap return x) == x' ?
How do you convince it that the current formulation of Monad obeys
the monad laws? (rhetorical)
--
brandon s. allbery [solaris,freebsd,perl,pugs,haskell] [EMAIL PROTE
Hello Neil,
Tuesday, February 5, 2008, 1:11:47 PM, you wrote:
> insert x y = delete x
> >>> deleteR y
> >>> unsafeInsert x y
i use the following trick:
(.$) = flip ($)
insert x y it = it.$ delete x
.$ deleteR y
.$ unsafeInsert x y
--
B
On Mon, 4 Feb 2008, Miguel Mitrofanov wrote:
> > Problem is that from the idea Functor is a superclass of Monad, with
> > the
> > property that "fmap == liftM".
>
> [cut]
>
> > The second relation can even not be expressed in Haskell 98.
>
> Erm...
>
> class Functor f where
> fmap :: (a -> b
On Mon, 4 Feb 2008 [EMAIL PROTECTED] wrote:
> On 2008.02.04 16:11:55 -0200, Maurício <[EMAIL PROTECTED]> scribbled 0.3K
> characters:
> > Hi,
> >
> > I've just tried using Haskore (I use Ubuntu
> > and GHC), with no success. Since Haskore was
> > started a long time ago, but it's not yet
> > ca
Neil Mitchell wrote:
> Yes, an MTL dependency is nothing to worry about at all, and isn't
> worth even thinking about removing given its actually used.
I would appreciate haskell98 portability!
We have a similar module, too, and would switch to a standard (if bimap
becomes it).
We've called it "
Hi
> > 1) You depend on MTL, but I can't obviously see why. Perhaps the test
> > suite?
>
> The current implementation of (!) relies on the Monad instance for
> Either exported by Control.Monad.Error. There's no fundamental reason
> for this; it was just easier to code. Perhaps I'll get rid of i
On Tue, 2008-02-05 at 00:10 -0500, Berlin Brown wrote:
> It looked like it passed the option, but didn't resolve the issue.
> Anyone seen that before? See error in previous post.
GHC is not a cygwin program. It does not use the cygwin gcc, it always
uses its own gcc anyway (which happens to be
On Tue, Feb 5, 2008 at 9:11 PM, Neil Mitchell <[EMAIL PROTECTED]> wrote:
> Hi
>
>
> > The main difference is a pretty comprehensive interface shakeup: the
> > Either variants have been dropped, all L variants have had the L
> > removed from their name, and a few functions have been curried. The
2008/2/5, Neil Mitchell <[EMAIL PROTECTED]>:
> 3)
> insert x y = delete x
> >>> deleteR y
> >>> unsafeInsert x y
>
> Why not:
>
> insert x y = unsafeInsert x y . delete x . delete y
>
> Now you don't end up using the arrow combinators, and it becomes more
> readable (at least to
Hello Matthew,
Monday, February 4, 2008, 11:45:51 PM, you wrote:
>> That would be nice. But its only beneficial if there are programs
>> which takes large amounts of stack at some point, but then shrink down
>> to very little stack and continue for a reasonable amount of time.
> From the 'when I
Hi
> The main difference is a pretty comprehensive interface shakeup: the
> Either variants have been dropped, all L variants have had the L
> removed from their name, and a few functions have been curried. The
> end result is an interface much closer to that of Data.Map. (This also
> means that 0
| > Yes, this is the standard solution, and it's a good one because it has a
robust cost model (no quadratic
| costs). However, it's tricky to get right; copying is simpler. If a
significant fraction of runtime (for some
| interesting program(s)) turned out to be consumed by copying stacks the
Simon Peyton-Jones wrote:
| First bad thing:
| Stack size (memory consumed) doubles each time it overflows.
|
| Second bad thing:
| Arbitrary limit on stack size unrelated to overall (heap) memory
| available.
|
| Third bad thing (the really bad thing):
| If a stack has temporarily grown (to 64M
| First bad thing:
| Stack size (memory consumed) doubles each time it overflows.
|
| Second bad thing:
| Arbitrary limit on stack size unrelated to overall (heap) memory
| available.
|
| Third bad thing (the really bad thing):
| If a stack has temporarily grown (to 64M say), it will never shrink
Stefan O'Rear wrote:
On Mon, Feb 04, 2008 at 10:13:12PM +, 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 only ne
59 matches
Mail list logo