[GHC] #824: overlapping instances and separate compilation

2006-07-11 Thread GHC
#824: overlapping instances and separate compilation ---+ Reporter: [EMAIL PROTECTED] |Owner: Type: bug | Status: new Priority: normal |

Re: [Haskell] problem building syb-generics

2006-07-11 Thread Matthew Pocock
On Tuesday 04 July 2006 13:20, Simon Peyton-Jones wrote: Lexically-scoped type variables are undergoing a slight upheaval in GHC 6.6 that has not quite settled, and that is what you are running into. Thanks for the help. After a lot of trial error, and reading and stuff I've got past the

Re: Is this test summary good or bad?

2006-07-11 Thread Joel Reymont
On Jul 11, 2006, at 11:00 AM, Simon Marlow wrote: Which ones hang? Could you take one of the hanging tests, compile it with -debug, run with +RTS -Ds, and send us the output? What ends up happening is this: 28683 p2 S 0:00.11 ../../timeout/timeout 300 cd ./typecheck/ should_compile

Re: RULES pragmas

2006-07-11 Thread Donald Bruce Stewart
Malcolm.Wallace: I have a question about {-# RULES #-} pragmas. Here is a very simple attempt to use them: module Simplest where {-# RULES simplestRule forall x. id (id x) = x #-} myDefn = id (id 42) I want to verify whether ghc-6.4.1 does actually fire

[Haskell] Lrc status

2006-07-11 Thread Robert Dockins
Does anyone have any information about the current status of Lrc? Has it ever been released? Does it live somewhere else now? The homepage is apparently: http://www.di.uminho.pt/~jas/Research/ LRC/lrc.html It has a bunch of coming soon links, but the page hasn't been updated since

[Haskell] crash unsafeperformio stm

2006-07-11 Thread Johannes Goetz
hi folks, i'm using ghc6 (apt-get install ghc6) on debian31. as far is i understand, the following program shouldn't crash. can somebody tell me why it does? thanks a lot. johannes. module Main(main) where import Control.Concurrent.STM import System.IO.Unsafe {-# NOINLINE a #-} a :: TMVar

Re: [Haskell] crash unsafeperformio stm

2006-07-11 Thread Taral
On 7/11/06, Johannes Goetz [EMAIL PROTECTED] wrote: i'm using ghc6 (apt-get install ghc6) on debian31. as far is i understand, the following program shouldn't crash. can somebody tell me why it does? thanks a lot. johannes. Because atomically doesn't like unsafePerformIO. For TVars there's

Re: [Haskell] crash unsafeperformio stm

2006-07-11 Thread Taral
On 7/12/06, Taral [EMAIL PROTECTED] wrote: Because atomically doesn't like unsafePerformIO. In more detail: atomically is not re-entrant. You could try something like: main = a `seq` do ... to make sure that you don't re-enter the STM subsystem and crash. -- Taral [EMAIL PROTECTED] You

[Haskell-cafe] instance Binary Data

2006-07-11 Thread Bulat Ziganshin
Hello Haskell, one Streams library user asked me about support of serialization TOGETHER with type information which means implementation of instance Binary Data (any other variants?). can anyone describe me how i can implement this? Binary instance is very like Show/Read, just uses compact

Re: [Haskell-cafe] Re: Why is there no splitBy in the list module?

2006-07-11 Thread Donn Cave
Quoth John Meacham [EMAIL PROTECTED]: ... | just a note: I find splitBy a much nicer routine to provide. | | splitBy :: (a - Bool) -- ^ whether char is a separator | - [a] -- ^ list to split | - [[a]] Starting from the assumption that in most cases the list to be split will be

Re: [Haskell-cafe] instance Binary Data

2006-07-11 Thread Joel Reymont
I don't see how this can work for arbitrary types without auto- generating the serialization code. Once the code is generated you can just store the type dictionary at the beginning of the file and use it to deserialize. I'm not sure this can be done on top of Binary since the type tag

[Haskell-cafe] Re: Why is there no splitBy in the list module?

2006-07-11 Thread Christian Maeder
John Meacham schrieb: just a note: I find splitBy a much nicer routine to provide. I would support this, if it helped to find a consensus. It's more difficult to decide if empty lists as elements of the result list (at the beginning, at the end or in the middle) should be returned. I would say

[Haskell-cafe] Small syntax question

2006-07-11 Thread Maurício
Hi, I can do this: (let a=3 in a) + (let b=4 in b) but not this: (a where a=3) + (b where b=3) Why? Thanks, Maurício ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Small syntax question

2006-07-11 Thread Thiago Arrais
Mauricio, The let variant is an expression, while the where one is not. An expression is allowed to happen inside a greater expression, you just need to place the parentheres properly as you did. The where keyword does not construct a valid expression, it can only happen inside some other

Re: [Haskell-cafe] Small syntax question

2006-07-11 Thread Thiago Arrais
By the way, you can find the syntax specification here http://haskell.org/onlinereport/syntax-iso.html Regards, Thiago Arrais -- Mergulhando no Caos - http://thiagoarrais.blogspot.com Pensamentos, idéias e devaneios sobre desenvolvimento de software e tecnologia em geral

Re: [Haskell-cafe] Defining show for a function type.

2006-07-11 Thread ihope
On 7/10/06, Fritz Ruehr [EMAIL PROTECTED] wrote: Were you interested in seeing the function, you could do so, at least for finite, total functions (you can also enumerate them, compare them for equality, etc.). See my haskell-cafe message at

[Haskell-cafe] Using of C constants in Haskell sources; Determining compilation environment (Unix vs Windows)

2006-07-11 Thread Bulat Ziganshin
Hello Haskell, what is a best way to bring C constant (defined in header file) into the Haskell source? Haskell project is cabalized and should work with both Win and Unix while the constants are OS-specific. the best way i found at this moment is to use the following scheme: mmap.h: #if

Re: [Haskell-cafe] Small syntax question

2006-07-11 Thread Bulat Ziganshin
Hello Maurício, Tuesday, July 11, 2006, 5:34:58 PM, you wrote: Hi, I can do this: (let a=3 in a) + (let b=4 in b) but not this: (a where a=3) + (b where b=3) Why? 'where' is a part of function definition syntax, while 'let .. in ..' is just an expression like 'if ...' or

[Haskell-cafe] technique to allow innocuous ambiguity in instance declarations?

2006-07-11 Thread Nicolas Frisby
Brief disclaimer: I'm using GHC 6.4.1 and haven't looked into Hugs; but I don't suspect there's much difference on this issue. Could easily be wrong there. I've hit a bit of a road bump in ambiguity regarding type class instances and transformer types (in the style of monad transformers). The

[Haskell-cafe] Re: Defining show for a function type.

2006-07-11 Thread Max Vasin
Johan == Johan Grönqvist [EMAIL PROTECTED] writes: Johan I am a haskell-beginner and I wish to write a Forth-like Johan interpreter. (Only for practice, no usefulness.) Johan I would like use a list (as stack) that can contain several Johan kinds of values. Johan data Element = Int Int | Float

[Haskell-cafe] Re: Using of C constants in Haskell sources; Determining compilation environment (Unix vs Windows)

2006-07-11 Thread Max Vasin
Bulat == Bulat Ziganshin [EMAIL PROTECTED] writes: Bulat Hello Haskell, what is a best way to bring C constant (defined Bulat in header file) into the Haskell source? Haskell project is Bulat cabalized and should work with both Win and Unix while the Bulat constants are OS-specific. the best way

[Haskell-cafe] comdlg32.dll FFI bindings

2006-07-11 Thread Jason Dagit
Hello, I was planning to create FFI bindings for GHC to be able to use comdlg32.dll and I just realized I should ask if others have already done this. I figure I'll probably just code it up by hand assuming I can find suitable documentation but if there is a tool that can generate this

Re: [Haskell-cafe] Using of C constants in Haskell sources; Determining compilation environment (Unix vs Windows)

2006-07-11 Thread Jeremy Shaw
At Tue, 11 Jul 2006 19:28:13 +0400, Bulat Ziganshin wrote: Hello Haskell, what is a best way to bring C constant (defined in header file) into the Haskell source? If this ^^^ was your entire question, I would say, use hsc2hs.

Re: [Haskell-cafe] Re: Why is there no splitBy in the list module?

2006-07-11 Thread Evan Laforge
splitBy :: (a - Bool) -- ^ whether element is a seperator - [a] -- ^ list to split - [[a]] P.S. inspecting more than one element looks like an over-generalization to me and should be left to parsers or regexp libs. It's more generally useful if you don't drop the separators

Re: [Haskell-cafe] comdlg32.dll FFI bindings

2006-07-11 Thread Neil Mitchell
Hi, There is a Win32 package which is shipped with WinHugs (and perhaps GHC as well). That may have the comdlg32.dll stuff in it, and if it doesn't that would be the place to add it, and it probably gives a good example of how to add it. Thanks Neil On 7/11/06, Jason Dagit [EMAIL PROTECTED]

[Haskell-cafe] Re: Why is there no splitBy in the list module?

2006-07-11 Thread Yitzchak Gale
I personally use split :: Eq a = [a] - [a] - [[a]] all the time, much more often than splitBy :: (a - Bool) - [a] - [[a]] But I don't call it split. By analogy with concatMap, the Haskell analogue of Perl/Python join is concatIntersperse. Then, by analogy with lines/unlines, the Haskell

Re: [Haskell-cafe] Re: Why is there no splitBy in the list module?

2006-07-11 Thread Jared Updike
split is... unconcatIntersperse. How about separate? (split or splitBy is better but it is used all over the place in many libs) And for strings I definitely would use split :: [a] - [a] - [[a]] a lot, just like Python's split function. And words works great for breaking on multiple spaces,

Re: [Haskell-cafe] Defining show for a function type.

2006-07-11 Thread Fritz Ruehr
On Jul 11, 2006, at 8:27 AM, ihope wrote: On 7/10/06, Fritz Ruehr [EMAIL PROTECTED] wrote: Were you interested in seeing the function, you could do so, at least for finite, total functions (you can also enumerate them, compare them for equality, etc.). See my haskell-cafe message at

[Haskell-cafe] Arrows and 'do' syntax

2006-07-11 Thread Greg Fitzgerald
I'm trying to translate this HXT code to use the Arrow 'do' syntax:readWriteDoc :: String - IOSLA (XIOState s) b IntreadWriteDoc path = readDocument [(a_validate, 0)] path writeDocument [(a_output_encoding, isoLatin1)] - getErrStatusThis attempt fails to compile: readWriteDoc :: String -

Re: [Haskell-cafe] comdlg32.dll FFI bindings

2006-07-11 Thread Jason Dagit
On 7/11/06, Neil Mitchell [EMAIL PROTECTED] wrote: Hi, There is a Win32 package which is shipped with WinHugs (and perhaps GHC as well). That may have the comdlg32.dll stuff in it, and if it doesn't that would be the place to add it, and it probably gives a good example of how to add it. The

Re: [Haskell-cafe] comdlg32.dll FFI bindings

2006-07-11 Thread Esa Ilari Vuokko
Hi Jason, On 7/12/06, Jason Dagit [EMAIL PROTECTED] wrote: The package you mention appears to ship with visual haskell but I don't see any wrappers for the functionality in comdlg32.dll. I would like to add that functionality. Do you know where I can find the source code for this package?

[Haskell-cafe] Breaking cycles in a directed graph.

2006-07-11 Thread Daniel McAllansmith
Hello. I'm currently using Data.Graph.Inductive to represent a directed graph. I want to detect all cycles within the graph and 'break' them by inserting a minimal number of nodes that are labelled with a special cycle-breaker label. Can anyone give me advice on a good algorithm for finding

[Haskell-cafe] Re: technique to allow innocuous ambiguity in instance declarations?

2006-07-11 Thread oleg
Nicolas Frisby posed a problem about controlling the order of instance selection rules (or, the application of type improvement rules) Given the following code newtype IdL a = IdL a newtype IdR a = IdR a class C f g where nest :: f a - g a instance C IdL IdR where nest (IdL x) = IdR x