Re: [Haskell-cafe] type error using ghc 6.10.1, not in previous versions

2009-01-12 Thread Anish Muttreja
On Mon, Jan 12, 2009 at 07:14:36PM -0800, Tim Bauer wrote: > Hi all. Under I have some old code that broke under ghc 6.10.1. > Under (6.6.1), 6.8.1 (and I think 6.8.2), this compiles. > > import Prelude hiding(catch) > import Control.Concurrent > import Control.Exception(catch,throw,evaluate) > > a

Re: [Haskell-cafe] ANN: bytestring-trie 0.1.4

2009-01-12 Thread wren ng thornton
Don Stewart wrote: Do you have any benchmarks comparing dictionaries against Map ByteString Int, or Map String Int? I haven't personally run them, but Mark Wotton has compared [(ByteString,Int)] vs (Map ByteString Int) vs (Trie Int) version 0.1.1 or 0.1.2 and using data from /usr/share/dict/w

[Haskell-cafe] ANN: json-0.4.1

2009-01-12 Thread Sigbjorn Finne
Hi, a new release of the 'json' package is now available via hackage, version 0.4.1 http://hackage.haskell.org/cgi-bin/hackage-scripts/package/json [no claims that it represents rocket science, but a number of downstream codebases depend on this package for their operation, hence the announce

[Haskell-cafe] type error using ghc 6.10.1, not in previous versions

2009-01-12 Thread Tim Bauer
Hi all. Under I have some old code that broke under ghc 6.10.1. Under (6.6.1), 6.8.1 (and I think 6.8.2), this compiles. import Prelude hiding(catch) import Control.Concurrent import Control.Exception(catch,throw,evaluate) async :: IO a -> IO (MVar a) async ioa = do mVar <- newEmptyMVar

Re: [Haskell-cafe] Multiple State Monads

2009-01-12 Thread David Menendez
On Mon, Jan 12, 2009 at 8:34 PM, Phil wrote: > Thanks Minh - I've updated my code as you suggested. This looks better than > my first attempt! > > Is it possible to clean this up any more? I find: > > ( (), (Double, Word64) ) > > a bit odd syntactically, although I understand this is just to fit

Re: [Haskell-cafe] Multiple State Monads

2009-01-12 Thread Luke Palmer
On Mon, Jan 12, 2009 at 6:34 PM, Phil wrote: > -- Monad Implementation > > evolveUnderlying :: (Double, Word64) -> ( (), (Double, Word64) ) > evolveUnderlying (stock, state) = ( (), ( newStock, newState ) ) > where >newState = ranq1Increment state >newStock = stock * exp ( ( ir - (0.5*(

Re: [Haskell-cafe] Functions with generic return types

2009-01-12 Thread Luke Palmer
On Mon, Jan 12, 2009 at 5:56 PM, Stephen Hicks wrote: > -- This instance definition is broken... > instance (Monad m,Pick (a,b) c) => Pick (m a,m b) (m c) where >pick (ma,mb) = do { a <- ma; b <- mb; return $ pick (a,b) } First, and I know these types of comments are generally unwanted, but

Re: [Haskell-cafe] Multiple State Monads

2009-01-12 Thread Phil
Thanks Minh - I've updated my code as you suggested. This looks better than my first attempt! Is it possible to clean this up any more? I find: ( (), (Double, Word64) ) a bit odd syntactically, although I understand this is just to fit the type to the State c'tor so that we don't have to write

[Haskell-cafe] Functions with generic return types

2009-01-12 Thread Stephen Hicks
Hi, I'm trying to write a small module for conveniently writing functions that can return any of a finite number of types. That is, I'd like to be able to write something like foo :: StringOrInt t => String -> IO t This is pretty easy to do if I hard-code the classes as above, but I run into di

Re: [Haskell-cafe] Looking for Haskellers on Windows

2009-01-12 Thread John Goerzen
Andrew Coppin wrote: > Günther Schmidt wrote: >> Hi Bulat, >> >> I do :), but I was amazed that there was no response to a post with, >> what I thought, would be a rather common problem for an application >> developer. That post was about writing to an MS-Access database via >> HDBC-ODBC, which

Re: [Haskell-cafe] Re: System.CPUTime and picoseconds

2009-01-12 Thread Peter Verswyvelen
I just tried getCPUTime on Windows and it seems to tick really slow, about 10 times per second or so. Actually it changes every 1560010 picoseconds, so about 15600 microseconds, which is indeed the interval at which Windows updates its "tick" count. So anyway a lot of room to go to the picoseco

Re: [Haskell-cafe] unfoldr [ANN: HLint 1.2]

2009-01-12 Thread Robin Green
On Mon, 12 Jan 2009 21:04:35 +0100 (CET) Henning Thielemann wrote: > > On Mon, 12 Jan 2009, Andrew Coppin wrote: > > > Off the top of my head, try this: > > > > convert b 0 = [] > > convert b n = n `mod` b : convert b (n `div` b) > > > > (Takes a number and yields the radix-B representation of

Re: [Haskell-cafe] Gtk2Hs on Windows for GHC 6.10.1

2009-01-12 Thread Duncan Coutts
On Tue, 2009-01-13 at 00:09 +0100, Peter Verswyvelen wrote: > Gtk2Hs 0.9.13 has an annoying bug on Windows that makes it impossible > to run via GHCi. > > > So to see if the latest development version works better, I tried to > build it on Windows using GHC 6.10.1, but I failed to do so with both

Re: [Haskell-cafe] Data analysis with Haskell

2009-01-12 Thread Luke Palmer
On Mon, Jan 12, 2009 at 2:16 PM, Daniel Kraft wrote: > This was probably my fault at that time, because I surely did something > completely wrong for the Haskell style. However, I fear I could run into > problems like that in the new project, too. So I want to ask for your > opinions, do you th

Re: [Haskell-cafe] Monads aren't evil? I think they are.

2009-01-12 Thread Philippa Cowderoy
On Sun, 2009-01-11 at 10:44 +0100, Apfelmus, Heinrich wrote: > Ertugrul Soeylemez wrote: > > Let me tell you that usually 90% of my code is > > monadic and there is really nothing wrong with that. I use especially > > State monads and StateT transformers very often, because they are > > convenient

[Haskell-cafe] Gtk2Hs on Windows for GHC 6.10.1

2009-01-12 Thread Peter Verswyvelen
Gtk2Hs 0.9.13 has an annoying bug on Windows that makes it impossible to run via GHCi. So to see if the latest development version works better, I tried to build it on Windows using GHC 6.10.1, but I failed to do so with both MSYS and Cygwin. Does anybody know how to build it on Windows? Thanks,

Re: [Haskell-cafe] ANN: HLint 1.2

2009-01-12 Thread Derek Elkins
On Mon, 2009-01-12 at 20:23 +0100, Bas van Dijk wrote: > On Mon, Jan 12, 2009 at 6:06 PM, Robin Green wrote: > > The fix-style equivalent to your repeat above, would be something like > > this: > > > > repeat x = fix $ \me -> x ::: me > > Interesting. The definition of fix is small and non-recur

[Haskell-cafe] Re: System.CPUTime and picoseconds

2009-01-12 Thread ChrisK
Tony Finch wrote: The FreeBSD kernel uses a 64+64 bit fixed point type to represent time, where the integer part is a normal Unix time_t. The fractional part is 64 bits wide in order to be able to represent multi-GHz frequencies precisely. "multi-GHz" being a euphemism for 18.45*10^9 GHz, over

Re: [Haskell-cafe] ANN: HLint 1.2

2009-01-12 Thread Derek Elkins
On Mon, 2009-01-12 at 19:43 +0100, Bas van Dijk wrote: > On Mon, Jan 12, 2009 at 6:47 PM, Max Bolingbroke > wrote: > > GHC should indeed be doing so. I'm working (on and off) to work out > > some suitable heuristics and put the transformation into ghc -O2. > > There are a few wrinkles that still n

Re: [Haskell-cafe] Re: [Haskell] ANN: ghci-haskeline 0.1

2009-01-12 Thread Andrew Hunter
On Mon, Jan 12, 2009 at 10:11:19PM +, ChrisK wrote: > Haskeline is designed to remove the readline dependency, because Windows > does not have readline. So rlwrap is useless there. > Ah, I hadn't considered Windows support--that makes sense. Thanks, that answers my questions. AHH

[Haskell-cafe] A pattern type signature cannot bind scoped type variables `t'

2009-01-12 Thread rodrigo.bonifacio
Hi all, I'm trying to build a library that has the following code: hasTypeOf (TermRep (dx,_,_)) (x::t) = ((fromDynamic dx)::Maybe t)   When I try to compile with ghc-6.8.3 I got the following error: ../../StrategyLib/models/drift-default//TermRep.hs:63:30: A pattern type signature cannot bind scope

Re: [Haskell-cafe] Re: [Haskell] ANN: ghci-haskeline 0.1

2009-01-12 Thread Roman Cheplyaka
* Andrew Hunter [2009-01-12 13:41:03-0800] > On Mon, Jan 12, 2009 at 12:57:57PM -0800, Judah Jacobson wrote: > > I'm pleased to announce the first release of ghci-haskeline. This > > package uses the GHC API to reimplement ghci with the Haskeline > > library as a backend. Haskeline is a library

[Haskell-cafe] Re: [Haskell] ANN: ghci-haskeline 0.1

2009-01-12 Thread ChrisK
Haskeline is designed to remove the readline dependency, because Windows does not have readline. So rlwrap is useless there. Andrew Hunter wrote: On Mon, Jan 12, 2009 at 12:57:57PM -0800, Judah Jacobson wrote: I'm pleased to announce the first release of ghci-haskeline. This package uses th

[Haskell-cafe] Re: [Haskell] ANN: ghci-haskeline 0.1

2009-01-12 Thread Andrew Hunter
On Mon, Jan 12, 2009 at 12:57:57PM -0800, Judah Jacobson wrote: > I'm pleased to announce the first release of ghci-haskeline. This > package uses the GHC API to reimplement ghci with the Haskeline > library as a backend. Haskeline is a library for line input in > command-line programs, similar t

Re: [Haskell-cafe] Data analysis with Haskell

2009-01-12 Thread Don Stewart
d: > Hi all, > > I'm going to start a project where I'll have to do some data analysis > (statistics about product orders) based on database entries; it will > mostly be some very basic stuff like grouping by certain rules and > finding averages as well as summing up and such. It will however

[Haskell-cafe] Data analysis with Haskell

2009-01-12 Thread Daniel Kraft
Hi all, I'm going to start a project where I'll have to do some data analysis (statistics about product orders) based on database entries; it will mostly be some very basic stuff like grouping by certain rules and finding averages as well as summing up and such. It will however be more than

Re: [Haskell-cafe] Fw: [darcs-devel] "Inferred type is less polymorphic than expected" and type witnesses

2009-01-12 Thread Ryan Ingram
Here's a minimal bit of code that gives you the error: > data FL p x z where > ConsFL :: p x y -> FL p y z -> FL p x z > NilFL :: FL p x x > data GTE a1 a2 x z where > GTE :: a1 x y -> a2 y z -> GTE a1 a2 x z > ccwo (ConsFL x xs) (ConsFL y ys) = >case ccwo xs ys of >GTE nx

Re: [Haskell-cafe] Multiple State Monads

2009-01-12 Thread minh thu
2009/1/12 Phil : > Hi, > > I've been reading the Monads aren't evil posts with interest – I'm a 2nd > week Haskell newbie and I'm doing my best to use them where (I hope) it is > appropriate. Typically I'm writing my code out without using Monads > (normally using list recursion), and then when I

[Haskell-cafe] haskell-platform mailing list

2009-01-12 Thread Duncan Coutts
Hi all, If you are interested in helping out with the haskell platform project then we invite you to subscribe to the haskell-platform mailing list. http://projects.haskell.org/cgi-bin/mailman/listinfo/haskell-platform This mailing list is for discussing practical stuff. We expect to discuss pol

Re: [Haskell-cafe] Re: Monads aren't evil? I think they are.

2009-01-12 Thread Henning Thielemann
Ertugrul Soeylemez schrieb: > "Apfelmus, Heinrich" wrote: > >> The insistence on avoiding monads by experienced Haskellers, in >> particular on avoiding the IO monad, is motivated by the quest for >> elegance. >> >> The IO and other monads make it easy to fall back to imperative >> programming pa

[Haskell-cafe] Multiple State Monads

2009-01-12 Thread Phil
Hi, I¹ve been reading the Monads aren¹t evil posts with interest ­ I¹m a 2nd week Haskell newbie and I¹m doing my best to use them where (I hope) it is appropriate. Typically I¹m writing my code out without using Monads (normally using list recursion), and then when I get them working, I delve in

Re: [Haskell-cafe] Monads aren't evil? I think they are.

2009-01-12 Thread Henning Thielemann
Apfelmus, Heinrich schrieb: > Ertugrul Soeylemez wrote: >> Let me tell you that usually 90% of my code is >> monadic and there is really nothing wrong with that. I use especially >> State monads and StateT transformers very often, because they are >> convenient and are just a clean combinator fron

Re: [Haskell-cafe] unfoldr [ANN: HLint 1.2]

2009-01-12 Thread Henning Thielemann
On Mon, 12 Jan 2009, Andrew Coppin wrote: Off the top of my head, try this: convert b 0 = [] convert b n = n `mod` b : convert b (n `div` b) (Takes a number and yields the radix-B representation of it. Backwards.) convert b = unfoldr (\n -> if n > 0 then Just (n `mod` b, n `div` b) else Not

[Haskell-cafe] Re: [Haskell] HaskellWiki Upgrade Aborted

2009-01-12 Thread Henning Thielemann
On Sun, 11 Jan 2009, Duncan Coutts wrote: We really need to upgrade the whole thing. Not an easy job given the range of stuff being run on there by lots of different people. Btw. is there a simple way to download all the Wiki content? ___ Haskell-Ca

[Haskell-cafe] unfoldr [ANN: HLint 1.2]

2009-01-12 Thread Andrew Coppin
Neil Mitchell wrote: Hi Andrew, HLint will automatically detect if you should have used a map, a foldr or a foldl and suggest how to change your code. In the GHC, darcs and Hoogle code bases there are no obvious map-like functions, which is a good sign :-) ...What an intriguing idea

Re: [Haskell-cafe] Generalized partial application (again)

2009-01-12 Thread Peter Verswyvelen
On Mon, Jan 12, 2009 at 8:33 PM, Felipe Lessa wrote: > > z1' = let f = (let y1 = e1 1; y2 = e2 2 in (\x -> op2 y2 y1 x)) in (f 3, f > 4) oooh! sweet! I didn't think of that. many thanks ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.

Re: [Haskell-cafe] Generalized partial application (again)

2009-01-12 Thread Felipe Lessa
How about using "let"s? 2009/1/12 Peter Verswyvelen : > e = trace "e" > op = (+) > a1 = let f = (op (e 1)) in (f 10, f 100) > a2 = let f = (\x -> op (e 1) x) in (f 10, f 100) > a1 and a2 are operationally not the same: a1 will evaluate (e 1) once, a2 a3 = let f = (let y = e 1 in (\x -> op y x)) i

Re: [Haskell-cafe] ANN: bytestring-trie 0.1.4

2009-01-12 Thread Don Stewart
Do you have any benchmarks comparing dictionaries against Map ByteString Int, or Map String Int? -- Don wren: > > -- bytestring-trie 0.1.4 > > > Another release for efficient finite maps from (byte)strings

[Haskell-cafe] Generalized partial application (again)

2009-01-12 Thread Peter Verswyvelen
Please correct me if I'm wrong in any of the reasoning below. Haskell provides the ability the perform partial application on the rightmost arguments. I learned from some pretty smart guys that partial application cannot be emulated with lambas, because they behave differently operationally, e.g.

Re: [Haskell-cafe] ANN: HLint 1.2

2009-01-12 Thread Bas van Dijk
On Mon, Jan 12, 2009 at 6:06 PM, Robin Green wrote: > The fix-style equivalent to your repeat above, would be something like > this: > > repeat x = fix $ \me -> x ::: me Interesting. Your repeat and mine are compiled to the same code: Data.Stream.repeat :: forall a_aVi. a_

Re: [Haskell-cafe] ANN: HLint 1.2

2009-01-12 Thread Henning Thielemann
On Mon, 12 Jan 2009, Robin Green wrote: I tend to use Control.Monad.Fix.fix (which actually has nothing to do with monads, despite the package name) That's why it is also available from Data.Function now: http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data-Function.html ___

Re: [Haskell-cafe] Question about touchForeignPtr

2009-01-12 Thread Patrick Perry
Thanks for your help, Duncan. On Jan 12, 2009, at 6:10 AM, Duncan Coutts wrote: Do the (ForeignPtr e) and the (Ptr e) point to the same thing? They appear to be related because you dereference p but touch f. It used to be the ForeignPtr was slower to dereference than a Ptr and so caching

Re: [Haskell-cafe] ANN: HLint 1.2

2009-01-12 Thread Robin Green
On Mon, 12 Jan 2009 19:43:00 +0100 "Bas van Dijk" wrote: > On Mon, Jan 12, 2009 at 6:47 PM, Max Bolingbroke > wrote: > > GHC should indeed be doing so. I'm working (on and off) to work out > > some suitable heuristics and put the transformation into ghc -O2. > > There are a few wrinkles that sti

Re: [Haskell-cafe] data, util, and lang packages

2009-01-12 Thread Don Stewart
rodrigo.bonifacio: >Hi all, I'm trying to build a library whose configuration process requires >the data, util, and lang packages. I guess that these are *deprecated* >packages, since the library is said to be ghc 6.4.1 compliant. > >Which packages should I use instead? > >Whe

Re: [Haskell-cafe] ANN: HLint 1.2

2009-01-12 Thread Jan-Willem Maessen
On Jan 12, 2009, at 12:47 PM, Max Bolingbroke wrote: 2009/1/12 Jan-Willem Maessen : On Jan 12, 2009, at 9:01 AM, Duncan Coutts wrote: No because the current definition are recursive and ghc cannot inline recursive functions. Then the map can be inlined at the call site and the 'f' i

[Haskell-cafe] data, util, and lang packages

2009-01-12 Thread rodrigo.bonifacio
Hi all, I'm trying to build a library whose configuration process requires the data, util, and lang packages. I guess that these are *deprecated* packages, since the library is said to be ghc 6.4.1 compliant. Which packages should I use instead? Where can I find such packages (if they are not depre

Re: [Haskell-cafe] ANN: HLint 1.2

2009-01-12 Thread Bas van Dijk
On Mon, Jan 12, 2009 at 6:47 PM, Max Bolingbroke wrote: > GHC should indeed be doing so. I'm working (on and off) to work out > some suitable heuristics and put the transformation into ghc -O2. > There are a few wrinkles that still need sorting out, but preliminary > indications are that it decrea

Re: [Haskell-cafe] ANN: HLint 1.2

2009-01-12 Thread Don Stewart
dons: > ndmitchell: > > Hi > > > > > Does GHC specialize map? If it doesn't, then hand crafted version > > > could be faster. > > > > GHC doesn't specialize map, and a hand-crafted one could be faster - > > but you then wouldn't get foldr/build fusion. In general HLint tries > > to make the code

Re: [Haskell-cafe] ANN: HLint 1.2

2009-01-12 Thread Don Stewart
ndmitchell: > Hi > > > Does GHC specialize map? If it doesn't, then hand crafted version > > could be faster. > > GHC doesn't specialize map, and a hand-crafted one could be faster - > but you then wouldn't get foldr/build fusion. In general HLint tries > to make the code prettier, but sometimes

Re: [Haskell-cafe] Fw: [darcs-devel] "Inferred type is less polymorphic than expected" and type witnesses

2009-01-12 Thread Rob Hoelz
I should've included these when I forwarded it, but that was pre-coffee today. =P class MyEq p where unsafeCompare :: p C(a b) -> p C(c d) -> Bool -- more stuff data FL a C(x z) where (:>:) :: a C(x y) -> FL a C(y z) -> FL a C(x z) NilFL :: FL a C(x x) data (a1 :> a2) C(x y) = FORALL(z)

Re: [Haskell-cafe] Fw: [darcs-devel] "Inferred type is less polymorphic than expected" and type witnesses

2009-01-12 Thread Ryan Ingram
Some questions first: What's the type of this function supposed to be? What's the type of unsafeCompare? How is the data type with NilFL and :>: defined? -- ryan On Mon, Jan 12, 2009 at 5:43 AM, Rob Hoelz wrote: > Forwarding to Haskell Cafe per Eric's suggestion. > > Begin forwarded message: >

Re: [Haskell-cafe] ANN: HLint 1.2

2009-01-12 Thread Max Bolingbroke
2009/1/12 Jan-Willem Maessen : > On Jan 12, 2009, at 9:01 AM, Duncan Coutts wrote: > >> No because the current definition are recursive and ghc cannot inline >> recursive functions. >> >> >> >> Then the map can be inlined at the call site and the 'f' inlined into >> the body of 'go'. > > This

[Haskell-cafe] Re: Question about touchForeignPtr

2009-01-12 Thread Simon Marlow
Patrick Perry wrote: I have the following code: IOVector n e = IOVector !ConjEnum !Int (ForeignPtr e)! (Ptr e)! Int! newtype Vector n e = IOVector n e unsafeAtVector :: Vector n e -> Int -> e unsafeAtVector (Vector (IOVector c _ f p inc)) i = let g = if c == Conj then conjugate else id

Re: [Haskell-cafe] ANN: HLint 1.2

2009-01-12 Thread Jan-Willem Maessen
On Jan 12, 2009, at 9:01 AM, Duncan Coutts wrote: No because the current definition are recursive and ghc cannot inline recursive functions. map :: (a -> b) -> [a] -> [b] map _ [] = [] map f (x:xs) = f x : map f xs It has to be manually transformed into a version that is not recursive at

Re: [Haskell-cafe] ANN: HLint 1.2

2009-01-12 Thread Henning Thielemann
On Mon, 12 Jan 2009, Neil Mitchell wrote: Hi No because the current definition are recursive and ghc cannot inline recursive functions. map :: (a -> b) -> [a] -> [b] map f = go where go [] = [] go (x:xs) = f x : go xs Then the map can be inlined at the call site and the 'f' inlin

Re: [Haskell-cafe] ANN: HLint 1.2

2009-01-12 Thread Duncan Coutts
On Mon, 2009-01-12 at 15:06 +0100, Henning Thielemann wrote: > > It has to be manually transformed into a version that is not recursive > > at the top level: > > > > map :: (a -> b) -> [a] -> [b] > > map f = go > > where > >go [] = [] > >go (x:xs) = f x : go xs > > > > Then the map c

Re: [Haskell-cafe] ANN: HLint 1.2

2009-01-12 Thread Neil Mitchell
Hi >> No because the current definition are recursive and ghc cannot inline >> recursive functions. > >> map :: (a -> b) -> [a] -> [b] >> map f = go >> where >> go [] = [] >> go (x:xs) = f x : go xs >> >> Then the map can be inlined at the call site and the 'f' inlined into >> the body of

Re: [Haskell-cafe] Question about touchForeignPtr

2009-01-12 Thread Duncan Coutts
On Sun, 2009-01-11 at 17:43 -0800, Patrick Perry wrote: > The "touchForeignPtr" is there to keep the garbage collector from > deallocating the memory before we have a chance to read 'e'. My > question is the following: > Is the `seq` on `io` necessary (from a safety standpoint)? Or am I > ju

Re: [Haskell-cafe] ANN: HLint 1.2

2009-01-12 Thread Henning Thielemann
On Mon, 12 Jan 2009, Duncan Coutts wrote: On Mon, 2009-01-12 at 01:02 +0100, Lennart Augustsson wrote: Does GHC specialize map? If it doesn't, then hand crafted version could be faster. No because the current definition are recursive and ghc cannot inline recursive functions. map :: (a ->

Re: [Haskell-cafe] ANN: HLint 1.2

2009-01-12 Thread Duncan Coutts
On Mon, 2009-01-12 at 01:02 +0100, Lennart Augustsson wrote: > Does GHC specialize map? If it doesn't, then hand crafted version > could be faster. No because the current definition are recursive and ghc cannot inline recursive functions. map :: (a -> b) -> [a] -> [b] map _ [] = [] map f (x:

[Haskell-cafe] Re: ANN: HLint 1.2

2009-01-12 Thread Juan Antonio Zaratiegui Vallecillo, a.k.a. Zara
Neil Mitchell escribió: > Hi > >> Does GHC specialize map? If it doesn't, then hand crafted version >> could be faster. > > GHC doesn't specialize map, and a hand-crafted one could be faster - > but you then wouldn't get foldr/build fusion. In general HLint tries > to make the code prettier, but

Re: [Haskell-cafe] version conflict on Hackage

2009-01-12 Thread Duncan Coutts
On Mon, 2009-01-12 at 13:21 +0100, Henning Thielemann wrote: > I repeatedly encounter the following versioning problem on Hackage: > There is a package A with version 1.0. > I upload a package B which imports A. > Thus B is bound to A-1.0 > Now a new version of A is uploaded, say 1.0.1. > then I up

[Haskell-cafe] Fw: [darcs-devel] "Inferred type is less polymorphic than expected" and type witnesses

2009-01-12 Thread Rob Hoelz
Forwarding to Haskell Cafe per Eric's suggestion. Begin forwarded message: Date: Sun, 11 Jan 2009 23:01:31 -0600 From: Rob Hoelz To: darcs-de...@darcs.net Subject: [darcs-devel] "Inferred type is less polymorphic than expected" and type witnesses Hello again, Darcs users and developers, As I

Re: [Haskell-cafe] Maintaining laziness

2009-01-12 Thread Henning Thielemann
On Mon, 12 Jan 2009, Jan Christiansen wrote: Hi, Although it seems to be overkill for a single module - How about a cabalized version on Hackage and a darcs repository? It would simplify using and updating it. I am not sure whether this would be a good idea. The original version makes a l

Re: [Haskell-cafe] Re: System.CPUTime and picoseconds

2009-01-12 Thread Tony Finch
On Mon, 12 Jan 2009, ChrisK wrote: > > Lennart is right that 1 picosecond accuracy is absurd compared to all > the jitters and drifts in anything but an actual atomic clock in your > room. But since CPUs tick faster than nanosecond the CPUTime needs > better than 1 nanosecond granularity. I agree

Re: [Haskell-cafe] Maintaining laziness

2009-01-12 Thread Jan Christiansen
Hi, Although it seems to be overkill for a single module - How about a cabalized version on Hackage and a darcs repository? It would simplify using and updating it. I am not sure whether this would be a good idea. The original version makes a lot of suggestions which are not satisfiable b

[Haskell-cafe] version conflict on Hackage

2009-01-12 Thread Henning Thielemann
I repeatedly encounter the following versioning problem on Hackage: There is a package A with version 1.0. I upload a package B which imports A. Thus B is bound to A-1.0 Now a new version of A is uploaded, say 1.0.1. then I upload package C which depends both on A and B. However C is bound to the

[Haskell-cafe] Error building Sdf2Haskell

2009-01-12 Thread rodrigo.bonifacio
Hi all, I'm trying to build the Sdf2Haskell library. However, I've got the following problem: Making all in generatorlocate: illegal option -- nusage: locate [-0Scims] [-l limit] [-d database] pattern ...default database: `/var/db/locate.database' or $LOCATE_PATHmake Sdf.tbllocate: illegal option -

[Haskell-cafe] Re: Computer time, independent of date

2009-01-12 Thread Mauricio
patients, I wanted to be sure not to save wrong information. It wouldn't matter if the clock is saying we are on XVII century, as long as 10 seconds would never be 10.1. What are the interval durations you need to measure? Since they are from equipment, what is the spec? I read from serial p

Re: [Haskell-cafe] Re: System.CPUTime and picoseconds

2009-01-12 Thread ChrisK
Neil Davies wrote: I've found the pico second accuracy useful in working with 'rate equivalent' real time systems. Systems where the individual timings (their jitter) is not critical but the long term rate should be accurate - the extra precision helps with keeping the error accumulation under

[Haskell-cafe] Re: System.CPUTime and picoseconds

2009-01-12 Thread Mauricio
Aren't Doubles evil? Integer is a nice type, Haskell filosofy compliant. Doubles are not CDoubles, IEEE, infinite precision or anything long term meaninfull. (Warning: non-expert opinion.) I've found the pico second accuracy useful in working with 'rate equivalent' real time systems. Systems whe

Re: [Haskell-cafe] Re: System.CPUTime and picoseconds

2009-01-12 Thread Neil Davies
I've found the pico second accuracy useful in working with 'rate equivalent' real time systems. Systems where the individual timings (their jitter) is not critical but the long term rate should be accurate - the extra precision helps with keeping the error accumulation under control. When

[Haskell-cafe] [ANNOUNCE] First release candidate of darcs 2.2.

2009-01-12 Thread Eric Kow
Dear Haskellers, I would like to forward this announcement on behalf of Petr Ročkai (the current darcs Release Manager). Darcs 2.2 is scheduled for release in 2009-01-15, only three days from now! This is the first of our biannual time-based releases. We hope you'll like it, and to help us ensu

[Haskell-cafe] Re: concurrent haskell: thread priorities

2009-01-12 Thread Simon Marlow
Neal Alexander wrote: Simon Marlow wrote: Neal Alexander wrote: Thomas DuBuisson wrote: It seems like we could get some priority based scheduling (and still be slackers) if we allow marked green threads to be strictly associated with a specific OS thread (forkChildIO?). I think

[Haskell-cafe] Re: concurrent haskell: thread priorities

2009-01-12 Thread Simon Marlow
Don Stewart wrote: marlowsd: Neal Alexander wrote: Thomas DuBuisson wrote: It seems like we could get some priority based scheduling (and still be slackers) if we allow marked green threads to be strictly associated with a specific OS thread (forkChildIO?). I think you want the GHC-

Re: [Haskell-cafe] ANN: HLint 1.2

2009-01-12 Thread Neil Mitchell
Hi > Does GHC specialize map? If it doesn't, then hand crafted version > could be faster. GHC doesn't specialize map, and a hand-crafted one could be faster - but you then wouldn't get foldr/build fusion. In general HLint tries to make the code prettier, but sometimes you will need to deviate fr

[Haskell-cafe] Re: how to link to external documentation with haddock ?

2009-01-12 Thread Dominic Steinitz
minh thu gmail.com> writes: http://www.haskell.org/haskellwiki/Haddock/FAQ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe