[Haskell] simple function: stack overflow in hugs vs none in ghc

2007-09-23 Thread Tom Pledger
John Lask wrote: : | The following code causes a "C stack overflow" in hugs (version 20051031) | but not in ghc (version 6.6) | The point of the exercise is to process a very large file lazily, | returning the consumed and unconsumed parts (i.e. basic parser combinators). : | > sqnc

Re: [Haskell] question about a failure to generalize

2007-09-16 Thread Tom Pledger
Quoting Stefan O'Rear <[EMAIL PROTECTED]>: On Mon, Sep 17, 2007 at 04:15:10PM +1200, Tom Pledger wrote: Norman Ramsey wrote: : | This code fails to compile because the compiler is willing to | use 'fold' at only one type (CmmExpr as it happens) : When it failed to c

[Haskell] question about a failure to generalize

2007-09-16 Thread Tom Pledger
Norman Ramsey wrote: : | This code fails to compile because the compiler is willing to | use 'fold' at only one type (CmmExpr as it happens) : When it failed to compile, was fold = foldRegsUsed a top-level declaration in the module, rather than local to foldRegsUsed? If so, try working

Re: [Haskell] newbie question: variable not in scope: "isSpace"

2004-08-14 Thread Tom Pledger
A.J. Bonnema wrote: If I use isSpace from the hugs interpretor, it works. If I use isSpace from a test.hs file I get the error message: Undefined variable "isSpace" From ghc I get the error message: Variable not in scope: "isSpace" What is wrong? Hugs automatically imports a few extra things as w

Re: [Haskell] State Transformers and Control.Monad.ST.Lazy

2004-06-22 Thread Tom Pledger
Vivian McPhail wrote: Hi, From the very helpful posts of John Hughes and others concerning "Monadic Loops", I've been advised to re-implement my neural net simulator using lazy state threads to avoid crashes to which recursive (and tail-recursive) monads lead. I had been using monad transforme

Re: [Haskell] Annoying naming clashes

2004-06-16 Thread Tom Pledger
John Meacham wrote: [...] I find trying to draw analogies between haskell classes and constructs in other languages to be problematic as people then try to apply knowledge from other fields incorrectly to haskell unless you give a full explanation of haskell classes anyway.. but YMMV. John

Re: [Haskell] Annoying naming clashes

2004-06-16 Thread Tom Pledger
[EMAIL PROTECTED] wrote: Tom, Then what will you do when naming operations in a class? Is it right that care has to be taken in order not to conflict with other classes? Say, I have a Person class where I want to define an operation "getName". Is it wise to name it "getPersonName" instead? Class me

Re: [Haskell] Annoying naming clashes

2004-06-11 Thread Tom Pledger
[EMAIL PROTECTED] wrote: Hi, when writing haskell code. It is so annoying that name clashes keep happening. I have to be careful about the data constructor names, about the class names, about the class member names. [...] As a novice haskell programmer, I might be missing something here though. If

Re: [Haskell] a newbie question

2004-04-26 Thread Tom Pledger
[EMAIL PROTECTED] wrote: Hi there. I got this question while I'm messing around with my toy monad. I was thinking about creating a generic monad that can persist state change even when fail is called. The StateT monad will discard the state change so it makes it hard to add tracing to the progra

Re: [Haskell] Per-type function namespaces (was: Data.Set whishes)

2004-03-05 Thread Tom Pledger
tion was magnitude v = v(.x, .y) <| sqrt (x*x + y*y) which was quite similar to Cayenne's "open ... use ... in ..." feature. Regards, Tom Pledger ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell] updating graphs non-destructively

2004-02-16 Thread Tom Pledger
S. Alexander Jacobson wrote: In imperative languages, updating an object in a graph is an O(1) operation. However, non-destructive update appears to be O(n) with the size of the graph. For example, suppose we were to implement an auction system like eBay: [snip] One alternative is to store poin

constrained datatype

2004-01-14 Thread Tom Pledger
Wang Meng writes: : | > class Foo n | > data Erk n = Foo n => Erk | | test.hs:53: | All of the type variables in the constraint `Foo n' are already in | scope | (at least one must be universally quantified here) : | Is there any reason for this error? I think it implies that

set representation question

2003-11-11 Thread Tom Pledger
Hal Daume III writes: : | *all* i care about is being able to quickly calculate the size of | the intersection of two sets. these sets are, in general, very | sparse, which means that the intersections tend to be small. | | for example, i might have two sets reprsented by the arrays: | |

RE: Expiring cached data?

2003-11-04 Thread Tom Pledger
[EMAIL PROTECTED] writes: | G'day all. | | Tom Pledger wrote: | | > How about adapting splay trees so that their pointers become weak | > after a certain depth? The advantage for caching is that the more | > frequently used elements move closer to the root, so you wouldn&

RE: Expiring cached data?

2003-11-03 Thread Tom Pledger
Conal Elliott writes: | Hi Andrew. This situation is what weak pointers [1] are for. You keep | weak rather than regular pointers to your cache data. The garbage | collector clears out the weak pointers and reclaims cache data when | necessary. However, I don't think there is any policy to

Re: The Future of Haskell discussion at the Haskell Workshop

2003-09-09 Thread Tom Pledger
Hi. Here's another opinion for the "Records! Records!" chorus: - The record and module system is one of the two big things I'd like to see changed in Haskell. (OT: the other is subtyping.) - It shouldn't happen before Haskell 2, because of backward compatability. (The dot operator

Re: overlapping instances and functional dependencies

2003-08-21 Thread Tom Pledger
C T McBride writes: : | but I'm not allowed | | class Bad x y z | x y -> z | | instance Functor f => Bad (f x) (f y) Bool | | instance Functor f => Bad x (f y) Int | | I don't quite see why. Naively, I imagine that if the OK instances are | effectively prioritized, then Bad's r

Re: Function composition and currying

2003-07-17 Thread Tom Pledger
K. Fritz Ruehr writes: : | But Jerzy Karczmarczuk enlightened me as to the full generality possible | along these lines (revealing the whole truth under the influence of at | least one beer, as I recall). Namely, one can define a sequence of | functions (let's use a better notation now, with "

Re: Collecting values from Functors?

2003-06-05 Thread Tom Pledger
Tomasz Zielonka writes: | On Wed, Jun 04, 2003 at 08:38:29PM +0200, Tomasz Zielonka wrote: : | > Or a variant of Functor constructor class that I have proposed some time | > ago on comp.lang.functional: | > | > class FunctorM t where | > fmapM :: Monad m => (a -> m b) -> (t a -> m (t b)

forall quantifier

2003-06-05 Thread Tom Pledger
Ketil Z. Malde writes: : | classify :: Eq b => [a->b] -> [a] -> [[[a]]] | classify cs xs = ... | | where for each classifying function in cs, I would get the xs | partitioned accordingly. E.g. | | classify [fst,snd] [(1,0), (1,2), (2,0)] | | would yield | | [ [(1,0), (1,2)

Arbitrary precision reals?

2003-03-24 Thread Tom Pledger
Niall Dalton writes: | Hi, | | Its been a while since I've been using Haskell seriously, so I might simply | have overlooked the answer.. | | Is there an arbitrary precision real number library available for Haskell? | IIRC, atleast GHC uses the GMP library, but only for integers? Hi. Th

Question about scope of 'let' and 'where'

2003-03-17 Thread Tom Pledger
Graham Klyne writes: | In the function body (rhs): | | let | { a = (e1) } | in | (e2) | where | { b = f a } : | : | I now see that use of 'where' is restricted to specific contexts. I wonder | if such restriction is needed? The diffe

Re: How to search for a string sequence in a file a rewrite it???

2003-03-13 Thread Tom Pledger
I've replied to this in haskell-cafe. Alexandre Weffort Thenorio writes: : | But I get this error saying: | | Expected Type: [String] | Inferred Type: String : ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/has

polymorphic type in state of state monad

2003-03-10 Thread Tom Pledger
Wang Meng writes: | Hi All, | | Any one of your have the experience of defining a state of a state monad | as a polymorphic type? | I want to have: | | > type State = Term a => [a] | > data M a = M (State -> IO(State,a)) | | GHC yields a error message "Illegal polymorphic type". | How

Re: data vs. newtype, abstractly

2003-03-09 Thread Tom Pledger
Dean Herington writes: : | My question came up in the context of describing such an abstract type for | users of the type. Like many others, I like to include actual Haskell | code where appropriate in the documentation. It didn't seem right to | commit there to either `data` or `newtype`.

Re: Evaluation Question

2003-01-12 Thread Tom Pledger
Hal Daume III writes: : | So, you're probably better off with: | | > nco wn = nco' | > where wn' = cis wn | > nco' = 1 : map (wn'*) nco' | | In which case it will only be evaluated once. The following version also evaluates 'cis wn' only once. > nco wn = iterate (cis wn *) 1 I've

Re: Field labels must be globally unique?

2003-01-07 Thread Tom Pledger
A third way is to put each datatype declaration in a separate module and use qualified imports. ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: How to force recursion

2002-12-09 Thread Tom Pledger
Cai john writes: : | what I want to do is eliminate b,c & d into a | recursive function: | | insertList tree [] = Empty | insertList tree (x:xs) = insertList(insert tree x) | | but hugs is complaining about a top-level overloading | error.Any idea how to fix it, thanks. I don't see

Re: AW: slide: useful function?

2002-12-02 Thread Tom Pledger
Nick Name writes: : | Ok I can't resist longer. It's ages I have been wondering what's a | catamorphism, and an anamorphism, and what the hell does it mean | "data is expressed by destructors and not by constructors", but I | have had no time till now. Please some of you all catamorphism | ex

idiom for different implementations of same idea

2002-08-01 Thread Tom Pledger
Hal Daume III writes: | Hi all, | | I'm looking for some advice on what's the cleanest way to implement | something. : | where the main driver does something like: | | prepareData | initialize | iterate until converged | doThingOne | doThingTwo | getResults | | As

encapsulation

2002-07-07 Thread Tom Pledger
Mark Fielder writes: | How does Haskell provide encapsulation? What mechanisms does it | use? The ways that spring to mind are modules and nested declarations: http://haskell.cs.yale.edu/onlinereport/modules.html http://haskell.cs.yale.edu/onlinereport/decls.html#sect4.4 | What are

reverse function application

2002-06-11 Thread Tom Pledger
Hal Daume III writes: : | 5 *== \x -> 6 *== \y -> somefunctiononxandy x y | | but i'd really like to be able to write: | | 5 *== 6 *== somefunctiononxandy : | any advice? If you want to do something akin to currying, to eliminate the explicit lambdas, I think you'll have to clutter up t

functional programming contest

2002-04-04 Thread Tom Pledger
Andre W B Furtado writes: | I was visiting http://www.ai.mit.edu/extra/icfp-contest/ and noticed that | there was a functional programming contest in ICFP 98. I'd like to know if | there are any periodic functional progamming contests around the world, such | as the ACM contest for the C langu

pattern-matching with labelled types

2002-03-07 Thread Tom Pledger
Andre W B Furtado writes: : | Of course, it is possible to do something like | | > update :: MyType -> Int -> MyType | > update mt newValue = MT {x = newValue, y = oldValue} | > where oldValue = y mt | | but this really annoys me when MyType has too many fields. Suggestions? update

Lazy Evaluation

2002-03-03 Thread Tom Pledger
Nguyen Phan Dung writes: : | mylist :: [Integer] | mylist = [1..10] | | In Hugs, I type mylist to print out all the elements inside. However, | after printing about 22000 elements, the system crashs & outputs: | "Garbage collection fails to reclaim sufficient memory" The declarati

Behavior of fromInteger on out-of-range arguments

2002-02-26 Thread Tom Pledger
David Feuer writes: : | Question: Is there any standard way in Haskell of determining the | maximal and minimal Int values? Yes, instance Bounded Int, which means you can use maxBound :: Int and minBound :: Int ___ Haskell mailing list [E

Composition Monad

2002-02-17 Thread Tom Pledger
Andre W B Furtado writes: | Roughly speaking, I'm in need of a monad (say MyIO) that interprets the | following code | | >f :: MyIO () | >f = do | >action1 | >action2 | >action3 | >... | >return () | | | as applying action1 to g, then action2

question about kinds

2002-01-20 Thread Tom Pledger
Hal Daume III writes: | Now, I want to say that if some data type 'd' is Traversable and | another data type 'e' is Traversable, then the "combined data type" | is Traversable. That is, for example, I want to say that a Tree of | Lists is traversable, or that a List of Trees, or a List of Lis

Re: Enum class

2001-10-23 Thread Tom Pledger
Jan-Willem Maessen writes: | * Split the Enum class into two. Possibly "correspondence with Int" | belongs in "Bounded"---but it depends what you think "Bounded" | means. FWIW I sometimes use a data type for the very purpose of adding bounds to an open-ended type. data Close a

Working character by character in Haskell

2001-10-18 Thread Tom Pledger
Andre W B Furtado writes: : | copyFile :: String -> String -> IO String | copyFile [] s = return (reverse s) | copyFile (a:as) s = copyFile as ( (doSomeStuffWith a):s) : | For example, suppose function doSomeStuffWith returns its own | parameter. Using a 1.5MB file in this case, the Haskel

Constructor class

2001-10-18 Thread Tom Pledger
Raul Sierra writes: | Hi all, | | What is the difference between regular classes and constructor classes | and how do you specify that a class is a constructor class? | | Thanks in advance, | Raul The term `constructor class' is meant to include classes like Functor and Monad, whose ins

Re: Extensible downcasts impossible in Haskell?

2001-10-09 Thread Tom Pledger
Thanks for the further explanation, Marcin. If I understand correctly, you're talking about explicitly named algebraic types, not just unions where the type is an anonymous reflection of the structure as in: Var (foo :: Int, bar :: Char) -- in the style of "A Polymorphic Type System for

Extensible downcasts impossible in Haskell? (was Re: Monomorphism, monomorphism...)

2001-10-08 Thread Tom Pledger
Marcin 'Qrczak' Kowalczyk writes: : | Since OO languages often use subtypes to emulate constructors of | algebraic types, they need downcasts. In Haskell it's perhaps less | needed but it's a pity that it's impossible to translate an OO | scheme which makes use of downcasts into Haskell in an

Re: 0-based versus 1-based

2001-09-27 Thread Tom Pledger
Thanks for the replies. I keep forgetting to read (!!1) as "the element at 1" and not as "the 1st element". ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

0-based versus 1-based

2001-09-27 Thread Tom Pledger
Just as a matter of idle curiosity, is there a particular reason for tuples starting at element 1 (fst) whereas lists start at element 0? fst ('x', 'y') --> 'x' "xy" !! 1 --> 'y' ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskel

type classes and generality

2001-07-09 Thread Tom Pledger
Norman Ramsey writes: : | how can I show that if a type has class Real, it also has class | Random.Random? Is there a way to accomplish this goal other than | by changing the library? How about the default-implementations-as-external-functions approach Marcin suggested, adapted for Real inst

Re: Haskell 98 Report

2001-05-30 Thread Tom Pledger
Zhanyong Wan writes: | Tom Pledger wrote: : | > deleteBy'' f = filter (not . f) | | No. deleteBy' f only deletes the *first* element that satisfies the | predicate f, while filter (not . f) deletes *all* such elements. Oops. Sorry. I ought to become

Re: Haskell 98 Report

2001-05-30 Thread Tom Pledger
Zhanyong Wan writes: : | I can't help wondering why it isn't | | deleteBy' :: (a -> Bool) -> [a] -> [a] | deleteBy' f [] = [] | deleteBy' f (y:ys) = if f y then ys else | y : deleteBy' f ys deleteBy'' f = filter (not . f) Malcolm Wallace

Recursive types?

2001-05-21 Thread Tom Pledger
David Bakin writes: | I'm having trouble understanding recursive types (e.g., as described in | Functional Programming with Overloading and Higher-Order Polymorphism by | Jones. | | He gives as an example | | | > data Mu f = In (f (Mu f)) | | > data NatF s = Zero | Succ s | > ty

typing question

2001-05-13 Thread Tom Pledger
Ben writes: : | (@@) :: (Num a) => Polynomial a -> a -> a : | the following doesn't work, | [ f @@ g | f <- poly, g <- poly, f /= g ] | where poly is a list of polynomials gives me, | | *** Expression : f @@ g | *** Term : f | *** Type : Polynomial Integer | *

Introducing a New Concept on Advanced Garbage Treatment Process

2001-04-19 Thread Tom Pledger
No, we already recycle, thanks. ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Concurrent Haskell (Ops...)

2001-04-16 Thread Tom Pledger
Andre W B Furtado writes: : | import Concurrent | | main :: IO() | main = let loop ch = putStr(ch) >> loop ch in |forkIO (loop "a") >> loop "z" | | But this program prints only 'z's, and no 'a's. I was surprised by | this, since GHC uses preemptive multitasking, not cooperative

Dimensional analysis with fundeps

2001-04-09 Thread Tom Pledger
I like it! : | 3) Allow arbitrary user-defined "fundamental" dimensions |(for things like dollars or radians) -- this may be |very tricky; | | 4) Allow several unit systems (such as SI and Imperial) |to coexist. Some suggestions/quibbles... If you clearly make the type syste

constants and functions without arguments

2001-03-29 Thread Tom Pledger
Andreas Leitner writes: : | Given a lazy pure functional language do we need to differntiate | (in syntax) between constants and functions without agruments? And | if we don't need to, does Haskell make a difference? Haskell always treats a declaration of the form foo = ... as a pattern

newbie

2001-03-08 Thread Tom Pledger
G Murali writes: | hi there, | | I'm new to this monads stuff.. can you tell me what it is simply ? | an example would be highly appreciated.. i want it is very very | simple terms please.. | | help please! There are some introductions to monads in the "Books and Tutorials about Program

Re: Fundeps and quantified constructors

2001-02-06 Thread Tom Pledger
nubie nubie writes: | | --- Tom Pledger <[EMAIL PROTECTED]> wrote: | > That line of reasoning establishes that e is constrained on the right | > hand side of the "=". However, it's still bound (by an implicit | > "forall e") on the left hand side of

Re: Are fundeps the right model at all?

2001-01-15 Thread Tom Pledger
Marcin 'Qrczak' Kowalczyk writes: > Mon, 8 Jan 2001 17:53:35 +1300, Tom Pledger <[EMAIL PROTECTED]> pisze: > > > > Having types with type variables which are never instantiated nor > > > constrained should be equivalent to having ground types! >

Just for fun

2001-01-09 Thread Tom Pledger
Anton Moscal writes: > Hello! > > This is well-known definition of the existential quantification > through universal: > > (E x.P(x)) <=> A y.(A x.P (x) => y) => y > > I try to translate in to Haskell. The following program can be > compiled by "ghc -fglasgow-exts ..." and works correc

Re: Are anonymous type classes the right model at all? (replying to Re: Are fundeps the right model at all?)

2001-01-08 Thread Tom Pledger
Marcin 'Qrczak' Kowalczyk writes: [...] > My new record scheme proposal does not provide such lightweight > extensibility, but fields can be added and deleted in a controlled > way if the right types and instances are made. Johan Nordlander must be on holiday or something, so I'll deputise fo

Yet more on functional dependencies

2001-01-08 Thread Tom Pledger
George Russell writes: > I am finding functional dependencies confusing. (I suspect I am not alone.) > Should the following code work? > > class HasConverter a b | a -> b where >convert :: a -> b > > instance (HasConverter a b,Show b) => Show a where >show value = show (convert

Are fundeps the right model at all?

2001-01-07 Thread Tom Pledger
Marcin 'Qrczak' Kowalczyk writes: > Could somebody show an example which requires fundeps and cannot be > expressed using a simpler model explained below - a model that I > can even understand? Is the model self-consistent at all? > [a model which uses key constraints instead of functional d

RE: Mutually recursive bindings

2000-11-09 Thread Tom Pledger
Tom Pledger writes: > Mark P Jones writes: > > [...] > > > > In general, I think you need to know the types to determine what > > transformation is required ... but you need to know the > > transformation before you get the types. Unless you break

Re: First class modules

2000-11-08 Thread Tom Pledger
Fergus Henderson writes: > On 07-Nov-2000, Tom Pledger <[EMAIL PROTECTED]> wrote: > > Supposing that (some version of) Haskell had first class modules, and > > type variables could be universally quantified at the module level, > > would rule 2 of the monom

First class modules

2000-11-06 Thread Tom Pledger
Hallo again. Supposing that (some version of) Haskell had first class modules, and type variables could be universally quantified at the module level, would rule 2 of the monomorphism restriction go away? Is this among the aims of the "First-class modules for component-based programming" (propos

RE: Mutually recursive bindings

2000-11-06 Thread Tom Pledger
Tom Pledger writes: > [...] > > For example, with FLAMV = free variables which will be lambda-bound, > and FLETV = free variables which will be let-bound, and ! marking the > alleged innovations: > > h = \x -> (x==

RE: Mutually recursive bindings

2000-11-05 Thread Tom Pledger
Mark P Jones writes: > [...] > > In general, I think you need to know the types to determine what > transformation is required ... but you need to know the > transformation before you get the types. Unless you break this > loop (for example, by supplying explicit type signatures, in which

Mutually recursive bindings

2000-11-05 Thread Tom Pledger
Hi. For this code (an example from the Combined Binding Groups section of Mark Jones's "Typing Haskell in Haskell"): f :: Eq a => a -> Bool f x = (x == x) || g True g y = (y <= y) || f True Haskell infers the type: g :: Ord a => a -> Bool but if the explicit type signature f

Mutually recursive structures

2000-10-16 Thread Tom Pledger
Timothy Docker writes: > [...] How can I do this in Haskell? If I don't have mutable > references, I figure that I must need to use laziness in some way, > perhaps similar to how I would build an infinite structure. http://www.mail-archive.com/haskell@haskell.org/msg06321.html I have nothing

Overlapping types

2000-08-23 Thread Tom Pledger
Tom Pledger writes: > [...] > > --Subtype should be transitive; I may have done something evil > --here, because Classic Hugs (November 1999) with the `-98' flag > --rejects this decl with the message `Undefined type variable "b"' >

Re: Overlapping types

2000-08-21 Thread Tom Pledger
Keith Wansbrough writes: > > class Subtype sub super where > > up :: sub -> super > > down :: super -> Maybe sub > > See the extensible union types of [Sheng Liang, Paul Hudak and Mark > Jones: Monad Transformers and Modular Interpreters] > > From the abstract: >

Overlapping types

2000-08-20 Thread Tom Pledger
The recent suggestion that OO and FP are somewhat out of phase reminds me of a pet topic: overlapping types. This is (IMHO) the only feature of OO for which there is (AFAICS) no FP equivalent. Here's a more concrete proposal than my previous vague rants on the subject. module Treat where

Re: The importance and relevance of FP

2000-08-18 Thread Tom Pledger
Florian Hars writes: > [...] Show me any working programmer who reads the "Improving > laziness"-part in the Hutton/Meijer paper on monadic parser > combinators and says "Oh! What an elegant language! And these nifty > efficiency improving no-ops like (fst (head x), snd (head x)): tail > x !"

monadic source of randomness

2000-08-09 Thread Tom Pledger
Norman Ramsey writes: > Does anybody know of work using monads to encapsulate a source of > random numbers? A quick web search suggested Haskell 98 did not take > this path. I'd be curious for any insights why, or any suggestions > about a `randomness monad'. > > > Norman Hi. Is the

Re: The type of zip

2000-08-03 Thread Tom Pledger
Hi. Claus Reinke writes: > - one would think that () simply takes its role as a unit, so that > (),a == a == a,() > but if we know x::() does that imply that x,a == a ? > x could be bottom, and the equations for the unit look strict in their > unit parameter, so probably not; Do

deriving Functor

2000-05-11 Thread Tom Pledger
Kuncak writes: > Why don't we have "deriving Functor" in Haskell? > > Functor is in Prelude, so it could be known to the compiler. > I am aware that one does not write modular interpreter every day, > but I think that turning a type constructor into functor is something > which is done quit

Impasse for math in Haskell 2

2000-04-30 Thread Tom Pledger
Jan Skibinski writes: > > It appears to me that we have reached some impasse > in a design of basic mathematical structure for > Haskell 2. Sergey's proposal "Basic Algebra Proposal" > is there, but for variety of reasons (a language > barrier being probably one of

Re: [wish list] Lightweight extensible records for Haskell

2000-03-30 Thread Tom Pledger
This is a bit belated, but... Marcin 'Qrczak' Kowalczyk wrote (Fri, 11 Feb 2000 04:05:58 -0800): > > Thu, 10 Feb 2000 23:17:13 +1100 (EST), [EMAIL PROTECTED] <[EMAIL PROTECTED]> pisze: > > > Could we please have lightweight extensible records for Haskell > > (as in the paper by (Mark|Simon

Re: newtypes

2000-03-16 Thread Tom Pledger
Marcin 'Qrczak' Kowalczyk writes: > Thu, 16 Mar 2000 14:38:30 -0500, Chris Okasaki <[EMAIL PROTECTED]> pisze: > > > How are these two statements reconciled for recursive > > types such as > > > > newtype Foo = F Foo > > IMHO simply the only value of this type is bottom. [...] Hi. Sh

Help! Is there a space leak here?

2000-02-23 Thread Tom Pledger
Hi. Joe English writes: > [...] ought to run in space bounded by the depth of the tree > (which for XML documents is typically not very deep). > > This turns out not to be the case; testing with Hugs > invariably fails with a "Garbage collection fails to > reclaim sufficient space" on even

Re: overlapping instances

2000-02-14 Thread Tom Pledger
Marcin 'Qrczak' Kowalczyk writes: > [...] However in the following case there is an ambiguity that I > don't know how to resolve - overlapping instances don't solve what > they seemed to claim to solve: > > classA a where ... > class A a => B a where ... > classC a where ..

[wish list] Lightweight extensible records for Haskell

2000-02-10 Thread Tom Pledger
[EMAIL PROTECTED] writes: > [...] > > Could we please have lightweight extensible records for Haskell (as > in the paper by (Mark|Simon Peyton) Jones in the 1999 Haskell > Workshop). Seconded. Symmetric record catenation, as opposed to extensibility by one field at a time, would make the H

Re: More on randoms

2000-02-04 Thread Tom Pledger
Jerzy Karczmarczuk writes: > [...] > I would love having 'next' returning reals as well... > And vectors (with decently uncorrelated elements). Etc. > > Do you think that all that must be manufactured by the user, or > can one parameterize the R. Gen. class a bit differently? Try making ea

RE: "Typo" in Haskell 98 Random library

2000-02-03 Thread Tom Pledger
Simon Peyton-Jones writes: > [...] > > Yes, that's a possible alternative. The current story says > "at least 30 bits"; you are suggesting [minBound..maxBound]. > In effect, you would mandate that every generator must have > genRange g = (minBound,msxBound). > > Seems like a reasonable a

Re: Everything which is both an X and a Y is also a Z

2000-02-03 Thread Tom Pledger
Marcin 'Qrczak' Kowalczyk writes: > Thu, 3 Feb 2000 14:24:28 +1300 (NZD), Tom Pledger <[EMAIL PROTECTED]> pisze: > > > instance (Bounded a, Enum a) => Random a where ... > > > But, every type in (Bounded, Enum) has a potential instance of Rand

Re: "Typo" in Haskell 98 Random library

2000-02-02 Thread Tom Pledger
Another afterthought: Matt Harden writes: > [...] compared to just knowing the RNG's range (which is almost > always fixed) ahead of time. [...] Yes, it would be useful to know the range ahead of time, so that we don't have to waste the extra guaranteed bits beyond the mandatory 30. Perhaps i

Re: "Typo" in Haskell 98 Random library

2000-02-02 Thread Tom Pledger
Matt Harden writes: > Tom Pledger wrote: > > [...] > > > > A similar approach can be taken, for getting uniform deviates (of > > types in Enum) from a generator in Haskell, without the bias. Just > > keep applying next, until you get an Int whose 30 trus

Everything which is both an X and a Y is also a Z

2000-02-02 Thread Tom Pledger
"Everything which is both an X and a Y is also a Z, and some other things are Zs too." Hi. This is not valid Haskell: import Random instance (Bounded a, Enum a) => Random a where ... because the class (Random) is applied directly to a type variable. But, every type in (Bounded, Enum)

"Typo" in Haskell 98 Random library

2000-02-02 Thread Tom Pledger
Hi. Simon Peyton-Jones writes: > [...] > > Suppose next produced output in the range 0..16. (It's specified > to produce "at least 30 bits", but the argument still holds.) > Suppose we want random numbers in the range 0..10. We can't just > take "mod 11" because that would produce too

partial ordering for Prelude. Reply

2000-02-01 Thread Tom Pledger
S.D.Mechveliani writes: > Tom Pledger <[EMAIL PROTECTED]> writes > > > May we please have a partial order class in Haskell at some stage? It > > can be done outside the prelude (see below), but would be nicer inside > > (see below, remo

Proposal for Haskell 2 prelude: partial ordering

2000-02-01 Thread Tom Pledger
{- Hi. May we please have a partial order class in Haskell at some stage? It can be done outside the prelude (see below), but would be nicer inside (see below, removing all the tildes and primes). Something similar could be done with abstract algebra above the Num and Fractional classes: Group

Specialisation by constraint [was: drop & take]

2000-01-26 Thread Tom Pledger
Hi. Marcin 'Qrczak' Kowalczyk writes, in reply to Ch. A. Herrmann: > > If using a natural type, people will insist on having a partial > > minus operation. How should the compiler check that this operation > > is well-defined? If the compiler can't, why have this type at all > > if the intege

Re: drop & take [was: fixing typos in Haskell-98]

2000-01-25 Thread Tom Pledger
Hi. For H98, I prefer option (A). Option (B) gives an arbitrary dissimilarity with rangeSize and enumFromTo. They currently match the standard mathematical treatment of ranges such as i..j, which Chris Okasaki mentioned. I'm not saying that they're sacred, just that a shift to the style of opt

Deprecated features

2000-01-24 Thread Tom Pledger
Sven Panne writes: > [...] So my suggestion is a new pragma DEPRECATED along the > following lines: [...] Opinions? I like it. Ideally, tools like HaskellDoc would also be aware of the DEPRECATED pragma.

Positive Num ?

2000-01-19 Thread Tom Pledger
Hi. I'm 80% confident in this reply, and 99% confident that someone will correct me if it's wrong or misleading. :-) Eileen Head writes: > Is there an easy way to define a new class, X, of types which is a > class of some range of types in an existing class Y. Yes, but only if the existing t

file manipulation

1999-12-06 Thread Tom Pledger
c_stanto writes: > > here is my code and I am guess that the problem is that openFile returns > an IO Handle and getContents takes just a Handle. How do I go about > fixing this? > > > module Main(main) where > > import IO > > main = putStrLn (getContents (openFile "./joseph.txt

The Haskell compiler of my dreams...

1999-11-24 Thread Tom Pledger
Let's keep this brief, if it's not going to be constructive. - Please correct me if I'm wrong: Clean is a proprietary language. - http://www.tuxedo.org/~esr/jargon/html/entry/troll.html

Incremental update for Array problems

1999-11-24 Thread Tom Pledger
c_stanto writes: > [...] > Error after type deriving/checking: > Type error type clash between Prelude.2 and Prelude.[] > when trying to apply function at 24:31 to its 2:nd argument at 24:34. > [...] > > type Entry = (String, String) > type HashTable = Array Int Entry > > [

New Haskell user

1999-11-21 Thread Tom Pledger
Hallo and welcome. c_stanto writes: > Can anyone tell me what is wrong with this code? > [...] There are some things there, which the compiler or interpreter will complain about. I suggest that you proceed by commenting it all out, then uncommenting a line or two at a time, and dealing with a

record lables overloading

1999-11-15 Thread Tom Pledger
S.D.Mechveliani writes: | [...] | But a large program is likely to have other data structures with | the same label names. [...] | | [...] | In such case, the compiler may report the ambiguity, and the | programmer may add the qualifier. | But in many other situtations, `up x' would be

Re: Dates in Haskell

1999-10-20 Thread Tom Pledger
George Russell writes: | [...] | Allowing a difference in days to be used as a number of months is | just going to cause confusion and bugs [...] Enough to last a month of Sundays? But seriously: Time is divided into intervals of irregular length, so operations like adding 1 month to "midday

  1   2   >