[Haskell-cafe] Re: Typeclasses and GADT [Was: Regular Expressions without GADTs]

2005-10-27 Thread Tomasz Zielonka
On 10/27/05, [EMAIL PROTECTED] [EMAIL PROTECTED] wrote: Tomasz Zielonka wrote: Speaking about casts, I was playing with using GADTs to create a non-extensible version of Data.Typeable and Data.Dynamic. I wonder if it's possible to write such a thing without GADTs (and unsafeCoerce,

[Haskell-cafe] RE: Instances That Ignore Type Constraints? (HList-related)

2005-10-27 Thread Ralf Lammel
Yeah, I was also thinking of impredicative types and that they would make this problem go away. First of all, we may need to wait a while for such types to become available in Haskell, but Daan has good stuff at avail. Also, for clarity, let me just point out that this is really about an

Re: [Haskell-cafe] Nice way to calculate character frequency in a string

2005-10-27 Thread Ketil Malde
Udo Stenzel wrote: That raises the question: Should combining functions on containers be provided in a strict variant? Should strict application be the default? With the exception of lists, I generally tend to want strict behavior for collections. Combined with the principle of least

Re: [Haskell-cafe] Nice way to calculate character frequency in a string

2005-10-27 Thread Ketil Malde
Scherrer, Chad wrote: Sorry to drag this thread out, but here's one more thing you might try... (This is the café, isn't it? :-) Another option is perhaps to pack both char and count in one Int and use some kind of Set. This should save some space, and possibly time as well (presuming

Re: [Haskell-cafe] lockFile: fd out of range

2005-10-27 Thread Joel Reymont
Actually, I think I was just hitting the top range of FD_SETSIZE, about 8000 on that machine. Does FD_SETSIZE get hardcoded into ghc-built binaries? That is if I increase the available descriptors per process with uname -n, will it be taken into account? Thanks, Joel On Oct 26,

Re: [Haskell-cafe] hs-plugins runtime loading issue

2005-10-27 Thread Joel Reymont
I believe it does. On Oct 26, 2005, at 1:32 AM, Donald Bruce Stewart wrote: Does the code work when you compile it, instead of running it inside ghci? -- http://wagerlabs.com/ ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org

[Haskell-cafe] Quickcheck examples and Data.Word32

2005-10-27 Thread Joel Reymont
Folks, Does anyone have QuickCheck examples they could send me? Also, how can I check Word32, Word64, etc. properties? It looks like the built-in random generator only works with Int values and for the life of me I cannot figure out how to extend it. Last but not least, I'm trying to

Re: [Haskell-cafe] Quickcheck examples and Data.Word32

2005-10-27 Thread Sebastian Sylvan
On 10/27/05, Joel Reymont [EMAIL PROTECTED] wrote: Folks, Does anyone have QuickCheck examples they could send me? Also, how can I check Word32, Word64, etc. properties? It looks like the built-in random generator only works with Int values and for the life of me I cannot figure out how to

[Haskell-cafe] Re: Quickcheck examples and Data.Word32

2005-10-27 Thread Shae Matijs Erisson
Joel Reymont [EMAIL PROTECTED] writes: Does anyone have QuickCheck examples they could send me? There's a minimal introduction to QuickCheck and HUnit in the most recent issue of The Monad.Reader: http://www.haskell.org/tmrwiki/IssueFive Also, how can I check Word32, Word64, etc. properties?

Re: [Haskell-cafe] Detecting Cycles in Datastructures

2005-10-27 Thread Lennart Augustsson
Tom Hawkins wrote: In a pure language, is it possible to detect cycles in recursive data structures? For example, is it possible to determine that cyclic has a loop? ... data Expr = Constant Int | Addition Expr Expr cyclic :: Expr cyclic = Addition (Constant 1) cyclic Or phased

[Haskell-cafe] Haskell scripting system (please help me simplify the design)

2005-10-27 Thread Joel Reymont
Folks, With lots of help from #haskell and haskell-cafe I came up with the following setup. It's working fine but requires quite a bit of boilerplate code. Could you please help me simplify it? I apologize for the very long message and will describe any parts that are unclear. Please ask

Re: [Haskell-cafe] Quickcheck examples and Data.Word32

2005-10-27 Thread Joel Reymont
Would it cover the range between minBound :: Word32 and maxBound :: Word32? I cannot figure out how to do this since maxBound :: Int32 is less that that of Word32. Also, I get the following error with ghci -fglasgow-exts foo.hs:7:52: parse error on input `.' -- module Foo where import

Re: [Haskell-cafe] Re: Quickcheck examples and Data.Word32

2005-10-27 Thread Joel Reymont
Is this gonna be in the next version of QuickCheck? Or can it be implemented now? On Oct 27, 2005, at 3:47 PM, Shae Matijs Erisson wrote: You can do that with the model based checking from the QuickCheckST paper. You could either generate actions and results and test separately, or you

[Haskell-cafe] Monads as control structures?

2005-10-27 Thread Creighton Hogg
Hi, so I'm a newbie getting used to Haskell. I'm writing some simple things like genetic algorithms in it for practice, and I keep coming across something that really bugs me: are there any standard libraries that allow you to do imperative style for or while loops using monads to keep

Re: [Haskell-cafe] Haskell scripting system (please help me simplify the design)

2005-10-27 Thread Robert Dockins
On Oct 27, 2005, at 11:01 AM, Joel Reymont wrote:Folks,With lots of help from #haskell and haskell-cafe I came up with the following setup. It's working fine but requires quite a bit of boilerplate code. Could you please help me simplify it?I apologize for the very long message and will describe

Re: [Haskell-cafe] Monads as control structures?

2005-10-27 Thread Björn Bringert
Creighton Hogg wrote: Hi, so I'm a newbie getting used to Haskell. I'm writing some simple things like genetic algorithms in it for practice, and I keep coming across something that really bugs me: are there any standard libraries that allow you to do imperative style for or while loops

Re: [Haskell-cafe] Monads as control structures?

2005-10-27 Thread ChrisK
Try this: This line is before the loop sequence_ $ replicate 10 $ do line 1 line 2 ... last line This line is after the loop Now you can use shorthand via loopN n block = sequence_ $ replicate n block So that you can write: This line is before the loop loopN 10 $ do line 1 line 2

Re: [Haskell-cafe] Haskell scripting system (please help me simplify the design)

2005-10-27 Thread Joel Reymont
Robert, On Oct 27, 2005, at 4:59 PM, Robert Dockins wrote: You could consider creating a monad for the unstuff part of the operation that would hide dealing with the FastString, the tupling and the case analysis on Maybe. Could you elaborate on this a bit please? How would I write and use

[Haskell-cafe] QuickCheckM for IO testing was Re: Quickcheck examples and Data.Word32

2005-10-27 Thread Shae Matijs Erisson
Joel Reymont [EMAIL PROTECTED] writes: I would very much like to see QuickCheckM extended to handle IO directly. I've wanted to use QuickCheck to test TCP/IP stacks for unhandled cases. Think of the entertainment value :-) Is this gonna be in the next version of QuickCheck? Or can it be

Re: [Haskell-cafe] Haskell scripting system (please help me simplify the design)

2005-10-27 Thread Joel Reymont
Something else just occurred to me... How would I represent no command using the Unstuff monad? I'm returning Maybe Command right now, would this change? On Oct 27, 2005, at 4:59 PM, Robert Dockins wrote: You could consider creating a monad for the unstuff part of the operation that would

Re: [Haskell-cafe] Monads as control structures?

2005-10-27 Thread Robert Dockins
On Oct 27, 2005, at 11:54 AM, Creighton Hogg wrote: Hi, so I'm a newbie getting used to Haskell. I'm writing some simple things like genetic algorithms in it for practice, and I keep coming across something that really bugs me: are there any standard libraries that allow you to do imperative

Re: [Haskell-cafe] Haskell scripting system (please help me simplify the design)

2005-10-27 Thread Cale Gibbard
On 27/10/05, Joel Reymont [EMAIL PROTECTED] wrote: On Oct 27, 2005, at 4:59 PM, Robert Dockins wrote: [snip] As a side note, I see you are doing a bunch of operations on lists of properties. If performance is an issue, you might want to consider using Data.Map or similar. If your

Re: [Haskell-cafe] Detecting Cycles in Datastructures

2005-10-27 Thread Tom Hawkins
Lennart Augustsson wrote: Tom Hawkins wrote: In a pure language, is it possible to detect cycles in recursive data structures? For example, is it possible to determine that cyclic has a loop? ... data Expr = Constant Int | Addition Expr Expr cyclic :: Expr cyclic = Addition (Constant 1)

Re: [Haskell-cafe] Monads as control structures?

2005-10-27 Thread Bryn Keller
Creighton Hogg wrote: Hi, so I'm a newbie getting used to Haskell. I'm writing some simple things like genetic algorithms in it for practice, and I keep coming across something that really bugs me: are there any standard libraries that allow you to do imperative style for or while loops

Re: [Haskell-cafe] Quickcheck examples and Data.Word32

2005-10-27 Thread Sebastian Sylvan
On 10/27/05, Joel Reymont [EMAIL PROTECTED] wrote: Would it cover the range between minBound :: Word32 and maxBound :: Word32? I cannot figure out how to do this since maxBound :: Int32 is less that that of Word32. Also, I get the following error with ghci -fglasgow-exts foo.hs:7:52: parse

Re: [Haskell-cafe] Quickcheck examples and Data.Word32

2005-10-27 Thread Sebastian Sylvan
On 10/27/05, Sebastian Sylvan [EMAIL PROTECTED] wrote: On 10/27/05, Joel Reymont [EMAIL PROTECTED] wrote: Would it cover the range between minBound :: Word32 and maxBound :: Word32? I cannot figure out how to do this since maxBound :: Int32 is less that that of Word32. Also, I get the

[Haskell-cafe] Coarbitrary (was QuickCheckM for IO testing)

2005-10-27 Thread Joel Reymont
How is this supposed to work? Does anyone have a simple explanation? I could not understand how to define this for arbitraries of my choosing and Shae seems to have defined coarbitrary = error Not implemented :-). Thanks, Joel -- http://wagerlabs.com/

Re: [Haskell-cafe] Detecting Cycles in Datastructures

2005-10-27 Thread Lennart Augustsson
Tom Hawkins wrote: Lennart Augustsson wrote: Tom Hawkins wrote: In a pure language, is it possible to detect cycles in recursive data structures? For example, is it possible to determine that cyclic has a loop? ... data Expr = Constant Int | Addition Expr Expr cyclic :: Expr cyclic =

Re: [Haskell-cafe] Quickcheck examples and Data.Word32

2005-10-27 Thread Joel Reymont
I came up with this but can it be done better? I'm wishing for default class methods :-). instance Arbitrary Word16 where arbitrary = arbitraryBound coarbitrary a = error Not implemented instance Arbitrary Word32 where arbitrary = arbitraryBound coarbitrary a = error Not

Re: [Haskell-cafe] Detecting Cycles in Datastructures

2005-10-27 Thread Iavor Diatchki
Hello, On 10/27/05, Tom Hawkins [EMAIL PROTECTED] wrote: ... data Expr = Constant Int | Addition Expr Expr cyclic :: Expr cyclic = Addition (Constant 1) cyclic ... And there is nothing that says that your definition of cyclic will actually have a cycle in the implementation.

Re: [Haskell-cafe] Quickcheck examples and Data.Word32

2005-10-27 Thread Bryn Keller
How about this? class ArbitraryDefault a where {} instance (Integral a, Bounded a, ArbitraryDefault a) = Arbitrary a where arbitrary = arbitraryBound coarbitrary a = error Not implemented instance ArbitraryDefault Word16 instance ArbitraryDefault Word32 instance ArbitraryDefault

Re: [Haskell-cafe] Quickcheck examples and Data.Word32

2005-10-27 Thread Joel Reymont
This requires {-# OPTIONS_GHC -fallow-undecidable-instances #-} but since I'm using -fglasgow-exts in a lot of places I'm wondering if adding undecidable instances would be a bad habit. I guess not... not until I shoot myself in the foot :-). Any explanation of undecidable instances, the

Re: [Haskell-cafe] Monads as control structures?

2005-10-27 Thread Creighton Hogg
On Thu, 27 Oct 2005, Creighton Hogg wrote: On Thu, 27 Oct 2005, Robert Dockins wrote: On Oct 27, 2005, at 11:54 AM, Creighton Hogg wrote: Hi, so I'm a newbie getting used to Haskell. I'm writing some simple things like genetic algorithms in it for practice, and I keep

Re: [Haskell-cafe] Quickcheck examples and Data.Word32

2005-10-27 Thread Bryn Keller
I've not had any problems with them, though of course your mileage may vary. Have a look at section 7.4.4.3 in http://www.haskell.org/ghc/docs/latest/html/users_guide/type-extensions.html#multi-param-type-classes for an explanation. Basically, if you have a cyclic class dependency graph, the

Re: [Haskell-cafe] Re: Coarbitrary

2005-10-27 Thread Nils Anders Danielsson
On Thu, 27 Oct 2005, Shae Matijs Erisson [EMAIL PROTECTED] wrote: Joel Reymont [EMAIL PROTECTED] writes: I could not understand how to define this for arbitraries of my choosing and Shae seems to have defined coarbitrary = error Not implemented :-). Coarbitrary is for generator

Re: [Haskell-cafe] Quickcheck examples and Data.Word32

2005-10-27 Thread Nils Anders Danielsson
On Thu, 27 Oct 2005, Sebastian Sylvan [EMAIL PROTECTED] wrote: instance Arbitrary Word32 where arbitrary = do c - arbitrary :: Gen Integer return (fromIntegral c) This definition will usually only generate very small or very large Word32 values. The reason is the wrapping

[Haskell-cafe] LINQ

2005-10-27 Thread Niklas Broberg
Why is it that everything that OO steals from the functional paradigm is always marketed as something new that will revolution the way we program? Can't they at least give some credit where credit is due? :-p

Re: [Haskell-cafe] LINQ

2005-10-27 Thread Lennart Augustsson
Because mentioning FP is the kiss of death? -- Lennart PS. I can see Eric Meijer's shadow behind this. ;) Niklas Broberg wrote: Why is it that everything that OO steals from the functional paradigm is always marketed as something new that will revolution the way we program? Can't

Re: [Haskell-cafe] Detecting Cycles in Datastructures

2005-10-27 Thread Nils Anders Danielsson
On Thu, 27 Oct 2005, Lennart Augustsson [EMAIL PROTECTED] wrote: Tom Hawkins wrote: Or phased differently, is it possible to make Expr an instance of Eq such that cyclic == cyclic is smart enough to avoid a recursive decent? No. And there is nothing that says that your definition of

Re: [Haskell-cafe] Detecting Cycles in Datastructures

2005-10-27 Thread Bulat Ziganshin
Hello Tom, Thursday, October 27, 2005, 6:46:41 PM, you wrote: TH In a pure language, is it possible to detect cycles in recursive data TH structures? no, but it is possible in GHC. Einar Karttunen in his SerTH - Binary Serialization library for Haskell used makeStableName and unsafeCoerce# to

Re: [Haskell-cafe] Monads as control structures?

2005-10-27 Thread Bulat Ziganshin
Hello Creighton, Thursday, October 27, 2005, 7:54:22 PM, you wrote: CH Haskell seems to me to be a very powerful language, and it CH looks like it should be possible to define control CH structures such as for loops using monads. it's my own lib: -- |Conditional execution whenM cond action =

Re: [Haskell-cafe] Nice way to calculate character frequency in a string

2005-10-27 Thread Benjamin Franksen
On Thursday 27 October 2005 10:29, Ketil Malde wrote: Scherrer, Chad wrote: Sorry to drag this thread out, but here's one more thing you might try... (This is the café, isn't it? :-) Another option is perhaps to pack both char and count in one Int and use some kind of Set. This should

[Haskell-cafe] hugs type inference

2005-10-27 Thread Christian Maeder
Hi, Hugs leaves an odd context when showing the type of the following expression. Is this a bug or just a harmless flaw? Christian Hugs.Base :t toRational 1 / 2 toRational 1 / 2 :: Real a = Ratio Integer ghci yields: Prelude :t toRational 1 / 2 interactive:1:0: Warning: Defaulting the

Re: [Haskell-cafe] Quickcheck examples and Data.Word32

2005-10-27 Thread Joel Reymont
Just one more question... data Prop = forall a b. (Eq a, Eq b, Show a, Packet b, Convertible a b) = Attr a b := a deriving (Typeable) data Attr a b = Attr String (a - Dynamic, Dynamic - Maybe a) (a - b, b - a) makeAttr :: (Typeable a, Convertible a b) = String - Attr a b

Re: [Haskell-cafe] hugs type inference

2005-10-27 Thread Ross Paterson
On Thu, Oct 27, 2005 at 11:02:48PM +0200, Christian Maeder wrote: Hugs.Base :t toRational 1 / 2 toRational 1 / 2 :: Real a = Ratio Integer ghci yields: Prelude :t toRational 1 / 2 interactive:1:0: Warning: Defaulting the following constraint(s) to type `Integer' `Real

Re: [Haskell-cafe] Quickcheck examples and Data.Word32

2005-10-27 Thread Joel Reymont
This compiles: instance (Typeable a, Arbitrary a, Typeable b, Arbitrary b, Convertible a b) = Arbitrary (Attr a b) where arbitrary = makeAttr `fmap` arbitrary coarbitrary a = error Not implemented arbitraryProp :: forall a b.(Eq a, Packet b, Show a, Convertible a b, Arbitrary a,

Re: [Haskell-cafe] Quickcheck examples and Data.Word32

2005-10-27 Thread John Meacham
On Thu, Oct 27, 2005 at 07:06:12PM +0100, Joel Reymont wrote: This requires {-# OPTIONS_GHC -fallow-undecidable-instances #-} but since I'm using -fglasgow-exts in a lot of places I'm wondering if adding undecidable instances would be a bad habit. I guess not... not until I shoot

Re: [Haskell-cafe] LINQ

2005-10-27 Thread John Meacham
On Thu, Oct 27, 2005 at 09:31:51PM +0200, Lennart Augustsson wrote: Because mentioning FP is the kiss of death? eh, no worse than mentioning cold fusion. :) John -- John Meacham - ⑆repetae.net⑆john⑈ ___ Haskell-Cafe mailing list