Re: Instances for String

1998-12-19 Thread Dylan Thurston
Sorry, I didn't read carefully enough. Your solution seems to work just fine, and do exactly what I want it to do. Thanks! --Dylan

Instances for String

1998-12-19 Thread Dylan Thurston
ork-arounds? Thanks, Dylan Thurston [EMAIL PROTECTED]

Re: Instances for String

1998-12-19 Thread Dylan Thurston
It is somewhat inconvenient but its not unfounded. You can use the technique used in the Show class in the Prelude to handle showing things of type String. Erik Meijer has written an exposition of this (which I can't find just now.) mike Here's an example. It elides the

Revamping the numeric classes

2001-02-06 Thread Dylan Thurston
equality. Think arbitrary precision reals. (I saw Mechvelliani's Basic Algebra Proposal; it strikes me as being too complicated for the task.) Best, Dylan Thurston ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo

Re: Revamping the numeric classes

2001-02-06 Thread Dylan Thurston
On Tue, Feb 06, 2001 at 10:29:36PM +0100, Andreas Gruenbacher wrote: On Tue, 6 Feb 2001, Dylan Thurston wrote: * (+) and (-) being lumped in with (*) (doesn't anyone use vector spaces?) That also causes me some headaches. ... Even for others, it might be scaling (s - t - t). It may

'Convertible' class?

2001-02-07 Thread Dylan Thurston
of the representation.) What do people think of this idea in general? Perhaps a better name would be 'Subtype'? Note that "convert . convert" would be up there with "show . read" as an ambiguous term. Best, Dylan Thurston ___ Haskell

Re: 'Convertible' class?

2001-02-07 Thread Dylan Thurston
On Wed, Feb 07, 2001 at 10:19:33PM +0100, Hannah Schroeter wrote: Hello! On Wed, Feb 07, 2001 at 03:43:59PM -0500, Dylan Thurston wrote: In thinking about various issues with the numeric classes, I came up with the following question: Is there a problem with having a class 'Convertible

Re: Revamping the numeric classes

2001-02-07 Thread Dylan Thurston
. 'quotRem' and 'divMod' are interesting cases: they return a pair (a,a), which is OK for some monads but not for others. I wonder if there is a way to set things up so that all classes could be written for monadic types. Best, Dylan Thurston

Types from values using existential types?

2001-02-09 Thread Dylan Thurston
to be ((exists a . (Singleton Int a) = a), (exists b . (Singleton Int b) = b)) for decidability. Are there any pointers to previous work I should look at? Thanks, Dylan Thurston ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org

Re: Types from values using existential types?

2001-02-10 Thread Dylan Thurston
Thanks for the very informative message! On Sat, Feb 10, 2001 at 06:37:03PM +1100, Fergus Henderson wrote: On 09-Feb-2001, Dylan Thurston [EMAIL PROTECTED] wrote: ... singleton returns a token of some new type; this token can then be passed around, stored in data structures, etc

Re: Type class inference trouble

2001-02-15 Thread Dylan Thurston
On Thu, Feb 15, 2001 at 02:37:09PM -0500, Ken Shan wrote: test2 = apply [int 3] (apply [(+)::Int-Int-Int] [int 5]) What's strange is that when I tried this just now, the identical line at the interpreter prompt returned the correct answer [8]. This is with Hugs from February 2000; I'm

Collection interfaces

2001-04-05 Thread Dylan Thurston
On Thu, Apr 05, 2001 at 01:18:48PM +0200, Marcin 'Qrczak' Kowalczyk wrote: ... I'm developing a unified collection interface (this is about a fifth try, but it finally seems to look well). ... Is it ready for public consumption? Best, Dylan Thurston

Re: Dimensional analysis with fundeps

2001-04-09 Thread Dylan Thurston
of view is that if you can do things like this painfully and explicitly in the current type system, Haskell might as well provide support to do it explicitly. Best, Dylan Thurston ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org

ghc 5.00 released??

2001-04-12 Thread Dylan Thurston
At http://haskel.org/ghc/, there seems to be an announcement for ghc 5.00, released April 9, 2001. Is this correct? I was surprised not to see an announcement posted here. (And this was just after I decided to compile the whole darn thing from CVS...) Best, Dylan Thurston

Re: Implict parameters and monomorphism

2001-04-24 Thread Dylan Thurston
scoped ?y). Is there some syntax for that (other than providing a type signature, which I agree is not desirable)? --Dylan Thurston ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: BAL paper available

2001-05-15 Thread Dylan Thurston
things could be done better (for instance, I see that all Sergey's classes derive from Eq, which is one of my principal complaints with the Haskell 98 classes), but I appreciate the work and want to study it more. Best, Dylan Thurston ___ Haskell

Re: Haskell Report (again)

2001-07-17 Thread Dylan Thurston
does not consider the case n 0). This suggests that there needs to be a code review of formatRealFloat, which I have not yet done. --Dylan Thurston ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Haskell Report (again)

2001-07-20 Thread Dylan Thurston
On Fri, Jul 20, 2001 at 04:59:05AM -0700, Simon Peyton-Jones wrote: Dale is absolutely right! How has this entirely bogus code survived so long? Err, my name is Dylan... Here is an (alleged) fix, which works in the tests I've tried. If anyone else can spare a moment to check my code I'd

Re: Haskell Report (again)

2001-07-20 Thread Dylan Thurston
On Fri, Jul 20, 2001 at 08:35:13AM -0700, Simon Peyton-Jones wrote: | (b) What is the code supposed to do? The code you posted always | prints a decimal point; I imagine this is intended? Can this be | documented? Sigh. The numeric library is entirely inadequately documented. I

Re: Haskell 98 Report possible errors, part one

2001-07-23 Thread Dylan Thurston
On Mon, Jul 23, 2001 at 06:30:30AM -0700, Simon Peyton-Jones wrote: | 2.2. Identifiers can use small and large Unicode letters. | What about caseless scripts where letters are neither small | nor large? The description of module Char says: For the | purposes of Haskell, any alphabetic

Re: series

2001-08-15 Thread Dylan Thurston
haven't find the way to do it. Here's a solution that uses continued fractions and uses much less memory than the other solutions proposed, though it is slow. Best, Dylan Thurston -- module E where type ContFrac = [Integer] Compute the decimal representation of e progressively

Re: type signatures with existentially quantified data constructors

2001-08-16 Thread Dylan Thurston
, Dylan Thurston ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Strange error in show for datatype

2001-10-04 Thread Dylan Thurston
On Wed, Oct 03, 2001 at 11:52:30AM -0400, Jan-Willem Maessen wrote: Earlier, Simon says: Indeed, if none of the classes have a method that returns an a-value without also consuming one (urk-- strictly, I think, sigh) then the same holds. Strictness alas matters. Here's the witness:

Re: Strange error in show for datatype

2001-10-04 Thread Dylan Thurston
to introduce such empty types for phantom-type purposes, so GHC now lets you say data T and get a type T with no values. Ah, excellent! I've frequently wanted to do this. Best, Dylan Thurston ___ Haskell mailing list [EMAIL PROTECTED] http

Re: H98: specialids and specialops

2001-10-04 Thread Dylan Thurston
'' are each a varid rather than a reservedid. They have special significance only in the context of an import declaration; they may also be used as variables. Best, Dylan Thurston ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org

Re: Unicode support

2001-10-05 Thread Dylan Thurston
of implementations is that they support 21 bits. Best, Dylan Thurston ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Haskell 98: Enum class

2001-10-24 Thread Dylan Thurston
On Wed, Oct 24, 2001 at 07:51:12AM -0700, Simon Peyton-Jones wrote: The Report is (regrettably) silent about what the Integer instances for succ and pred should be, but they should definitely simply add 1 (resp subtract 1). They should emphatically not use the default methods. I will add

Re: [ketil@ii.uib.no: Re: Enum class]

2001-10-25 Thread Dylan Thurston
(I want to trim the headers, but don't know the history of this thread. Also cc:ed back to the Haskell list.) On Thu, Oct 25, 2001 at 11:11:42AM +0200, Ketil Malde wrote: Dylan Thurston [EMAIL PROTECTED] writes: I agree that Enum instances for Float/Double are not likely to be useful

Re: Functional Metapost maintained?

2001-11-25 Thread Dylan Thurston
On Sat, Nov 24, 2001 at 04:52:00PM +0100, Ferenc Wagner wrote: BTW, I didn't notice import problems. They may be specific to GHC... I have got 5.02-1 now, I'll check later. I don't know if it's specific to GHC, but it's definitely a bug in Functional MetaPost (although probably easy to

Re: Arrow notation, etc.

2001-10-12 Thread Dylan Thurston
On Fri, Oct 12, 2001 at 12:39:09PM +0100, Keith Wansbrough wrote: Dylan writes: Incidentally, it seems to me that this is one case where a Lisp-like macro facility might be useful. With Haskell, it is impossible to play with bindings, while presumably you can do this with good Lisp

Re: Arrow notation, etc.

2001-10-12 Thread Dylan Thurston
need a macro for it in Lisp. Your arrow notation example may provide some motivation, though. I wonder if macros could also be used to implement views. I think there were other times I wanted to play similar tricks with scoping, but I don't remember right now. Best, Dylan Thurston

Re: Haskell 98 - Standard Prelude - Floating Class

2001-10-15 Thread Dylan Thurston
. (They don't work for floating point numbers because of the special behaviour near 0.) Best, Dylan Thurston ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: gcd 0 0 = 0

2001-12-18 Thread Dylan Thurston
they are defined (with gcd 0 0 = 0). As I said, I was surprised; to me, the definiton with all a and b is the more natural one. I still recommend using the full domain (especially since exceptions are awkward to deal with in Haskell), but I'm not as certain. Best, Dylan Thurston

Re: RFC: Syntax for implicit parameter bindings

2002-02-04 Thread Dylan Thurston
On Mon, Feb 04, 2002 at 01:33:54PM -0800, Ashley Yakeley wrote: At 2002-02-04 01:45, Koen Claessen wrote: | addBase{?base=7} 5 I like this! It is the least polluting syntax of all. Hmm... you have braces without following a keyword. I think in all other cases, braces follow a keyword

Re: ideas for compiler project

2002-02-16 Thread Dylan Thurston
for a variable, you don't have to figure out how to gather them together. Can anyone see a way to implement something like this in Haskell? Or is it better to make a small interpreted language? Best, Dylan Thurston msg10237/pgp0.pgp Description: PGP signature

Re: and do notation

2002-04-02 Thread Dylan Thurston
are typically prohibited from taking advantage of such laws, and why the translation from the 'do' notation should be the obvious one (using ''). Best, Dylan Thurston msg10610/pgp0.pgp Description: PGP signature

Re: Double - non-double function :)

2002-04-04 Thread Dylan Thurston
representation? --Dylan Thurston msg10624/pgp0.pgp Description: PGP signature

Re: preprocessing printf/regex strings (like ocaml)

2002-05-14 Thread Dylan Thurston
On Tue, May 14, 2002 at 03:45:36PM +0100, Robert Ennals wrote: Just thought I would jump in and say that, unlike (it seems) everyone else, I hate printf in C. It is a horrible horrible inextensible hack of a function that I find extremely awkward to use. ... I personally much prefer the

Re: State monads don't respect the monad laws in Haskell

2002-05-14 Thread Dylan Thurston
On Tue, May 14, 2002 at 04:57:12PM +0200, George Russell wrote: According to the report Instances of Monad should satisfy the following laws: return a = k = k m = return= m m = (\x - k x = h) = (m = k) = h so neither IO nor my events satisfy this. Up to

Re: State monads don't respect the monad laws in Haskell

2002-05-15 Thread Dylan Thurston
to laziness issues; your approach seems like a promising way to avoid that. Best, Dylan Thurston msg10904/pgp0.pgp Description: PGP signature

Re: ANN: Functional Metapost 1.2

2002-05-27 Thread Dylan Thurston
a horizontal distance of $1/9$ inch or approximately $2.82$ mm. This contradicts the table that immediately follows, in which it is evident that a unit of '1' is one printer's point, 1/72.27 of an inch; the Postscript points are called 'bp'. Which is correct? Best, Dylan Thurston

Re: idiom for different implementations of same idea

2002-08-01 Thread Dylan Thurston
On Thu, Aug 01, 2002 at 02:34:00PM -0700, Hal Daume III wrote: ... Now, I want in my executable my user to be able to say -model=0 and so on in the command line and for it to use the appropriate model. Each of these models will go in a separate module. One way to do this would be to

Re: zipWith, zipWith3, zipWith4.... looks gawky, IMHO

2002-08-19 Thread Dylan Thurston
On Sun, Aug 18, 2002 at 06:32:27PM +0200, [EMAIL PROTECTED] wrote: Hi all. I'm new to this mailing list. (and still a relative newbie in Haskell - learning GraphicsLib) Because the Wish List did not work (maybe it is my browsers fault), I now write it to this list. I found the zipWithN

Re: Evaluation order, ghc versus hugs, lazy vs. strict

2002-08-19 Thread Dylan Thurston
in constant space. I guess strictness analysis (which knows how to evaluate the foldl) only happens at -O2 or above? Best, Dylan Thurston ___ Haskell mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

Re: Evaluation order, ghc versus hugs, lazy vs. strict

2002-08-19 Thread Dylan Thurston
On Mon, Aug 19, 2002 at 11:34:48PM +0100, Alastair Reid wrote: main = print $ sum [0..100] ... Hugs uses foldl' instead of foldl to define sum:... Does it really? That's a violation of the standard: a user's instance of (+) need not be strict in its left argument. Consider data Foo

Re: Evaluation order, ghc versus hugs, lazy vs. strict

2002-08-21 Thread Dylan Thurston
) of the GHC user's manual. --Dylan Thurston msg11412/pgp0.pgp Description: PGP signature

Re: A question concerning functional dependencies

2002-09-02 Thread Dylan Thurston
On Mon, Sep 02, 2002 at 03:11:58AM -0700, Ashley Yakeley wrote: At 2002-09-02 02:46, Jerzy Karczmarczuk wrote: class Module v s | v-s . ... instance Num s = Module (v-s) s ... instance ...= Module ((v-s)-(v-s)) s ... But GHCi yells that two instances in view of the functional

Re: Haskell 98

2002-09-19 Thread Dylan Thurston
On Thu, Sep 19, 2002 at 02:36:01PM +0100, Simon Peyton-Jones wrote: The copyright notice is, I believe, agreed with CUP, but I must check that. The online versions will remain available. Will the online version be available with the current copyright, or will it only be available with the

Re: Field labels must be globally unique?

2003-01-12 Thread Dylan Thurston
. Best, Dylan Thurston msg12043/pgp0.pgp Description: PGP signature

Re: seeking ideas for short lecture on type classes

2003-01-27 Thread Dylan Thurston
[a]) (Tree [a]) in which the variable 'a' is used recursively at a different type.) Best, Dylan Thurston msg12142/pgp0.pgp Description: PGP signature

Re: two easy questions

2003-02-23 Thread Dylan Thurston
_ = True ? (The pattern matching doesn't work quite the same way, but you can use guards to acheive the same effect, especially with ghc's pattern guards extension.) Best, Dylan Thurston pgp0.pgp Description: PGP signature

Re: Multiparameter class confusion

2003-06-07 Thread Dylan Thurston
On Wed, Jun 04, 2003 at 01:21:00PM +0100, Graham Klyne wrote: There is a recurring difficulty I'm having using multiparameter classes. Most recently, I have a class Rule: [[ class (Expression ex, Eq (rl ex)) = Rule rl ex where ... ]] Which I wish to instantiate for a type GraphClosure

Re: Overlapping instances in existentials

2003-06-20 Thread Dylan Thurston
On Thu, Jun 19, 2003 at 11:08:35AM -0500, Ed Komp wrote: | type BaseType = Either Integer ( Either Bool () ) | | type Value = (Either Double BaseType) | | data Foo = forall x. (SubType x BaseType) = MkFoo x | | test :: Foo - Value | test (MkFoo x) = inj x 'x' is the

Re: How overload operator in Haskell?

2003-07-12 Thread Dylan Thurston
On Fri, Jul 11, 2003 at 05:38:18PM +1000, Andrew J Bromage wrote: G'day all. On Thu, Jul 10, 2003 at 11:16:56PM -0700, Ashley Yakeley wrote: As written, this is _not_ a good idea. Trust me, you end up having to put type annotations everywhere. Even (3 + 4 :: Integer) is ambiguous,

Re: User-Defined Operators, Re: Function composition and currying

2003-07-18 Thread Dylan Thurston
On Fri, Jul 18, 2003 at 11:39:48AM +1000, Andrew J Bromage wrote: Someone mentioned multiplying by a scalar. I think this is a good application, but what we need is to agree (somehow) on the symbol used. I've used (*.) and (.*), with the dot being on the side the scalar is on (on the

Re: User-Defined Operators, Re: Function composition and currying

2003-07-18 Thread Dylan Thurston
On Sat, Jul 19, 2003 at 02:06:44PM +1000, Andrew J Bromage wrote: G'day all. On Fri, Jul 18, 2003 at 04:08:25AM -0400, Dylan Thurston wrote: What's wrong with that solution? Working with these operators, I would spend a significant amount of time getting the '' and '' notations right

Re: Superclass Defaults

2003-07-21 Thread Dylan Thurston
On Mon, Jul 21, 2003 at 06:21:33AM -0700, Ashley Yakeley wrote: Well I don't doubt this would be a very useful extension to the Haskell language: indeed it would eliminate code in all my Haskell projects. But before we can propose this, we have to work out what the syntax would look like.

Re: [Haskell] Haddock, QuickCheck, and Functional Design by Contract

2004-03-21 Thread Dylan Thurston
(Reviving an old message here. You can see the original message at http://www.stud.tu-ilmenau.de/~robertw/haskell/doc/contract_notations.lhs ) On Tue, Feb 17, 2004 at 10:50:30AM +0100, Robert Will wrote: 4. A notation for preconditions. ... Presently I use the following coding style:

Re: [Haskell] Proposal for a Standard of Abstract Collections (with Reference Implementation)

2004-03-21 Thread Dylan Thurston
It looks interesting and I'm still looking at it, although I think many of the language extensions need to be better thought out. But it exhibits the creeping Eq problem: your hierarchy starts class (Eq (coll a), Eq a) = Collection coll a where ... If this is to replace lists, this is

Re: [Haskell] Proposal for a Standard of Abstract Collections (with Reference Implementation)

2004-03-22 Thread Dylan Thurston
Another comment is that it looks too complicated. Your basic Collection class has 30 members, and some of them are clearly excessive: do you really need all of has, elem, (#), not_elem, and (/#) in the class (rather than defined as auxiliary functions, possibly optimised with fusion)? (Of

[Haskell] Dynamically loading wxhaskell?

2004-03-31 Thread Dylan Thurston
Has anyone succeeded in getting wxhaskell to work under ghci on Linux? On my system, I get an error message Loading package unix ... ghc-6.2: can't load .so/.DLL for: dl (libdl.so: cannot open shared object file: No such file or directory) This sounds like it has nothing to do with wxhaskell,

Re: [Haskell] Dynamically loading wxhaskell?

2004-04-01 Thread Dylan Thurston
On Thu, Apr 01, 2004 at 10:00:23AM +0100, Simon Marlow wrote: Has anyone succeeded in getting wxhaskell to work under ghci on Linux? On my system, I get an error message Loading package unix ... ghc-6.2: can't load .so/.DLL for: dl (libdl.so: cannot open shared object file: No such

Re: [Haskell] ANNOUNCE: HaRP (Haskell Regular Patterns) version 0.1

2004-05-15 Thread Dylan Thurston
This looks very interesting! I sometimes wish Haskell had more powerful binding facilities, so that things like this don't need to be extensions to the language. (But I'm not sure exactly what I'm wishing for...) On Sat, May 15, 2004 at 12:08:53PM +, Niklas Broberg wrote: Introducing

Re: [Haskell] ANNOUNCE: HaRP (Haskell Regular Patterns) version 0.1

2004-05-15 Thread Dylan Thurston
On Sat, May 15, 2004 at 04:42:03PM +, Niklas Broberg wrote: In non-linear context, the type is a list of what it would otherwise be, regardless of what and how many enclosing non-linear regular pattern operators. So I guess that in foo [/ a? 2 b /] = (a,b) the type of a is

Re: [Haskell] for large x, log (x::Integer) :: Double

2004-07-04 Thread Dylan Thurston
On Wed, Jun 30, 2004 at 03:07:00PM -0700, Greg Buchholz wrote: -- Inspired from Mr. Howard Oakley. Might not qualify as good, -- but with this function I get log10(x)=849.114419903382 ... For those who aren't aware: working with logs base 2 internally will be very much faster than logs base

Re: [Haskell] for large x, log (x::Integer) :: Double

2004-07-11 Thread Dylan Thurston
On Mon, Jul 05, 2004 at 10:08:04AM +0100, Edmund GRIMLEY EVANS wrote: Does Haskell provide any means of determining the number of binary digits in an Integer other than by repeated division? See the Data.Bits library: http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data.Bits.html

Re: [Haskell] for large x, log (x::Integer) :: Double

2004-07-13 Thread Dylan Thurston
On Tue, Jul 13, 2004 at 05:01:32PM +0800, Dylan Thurston wrote: This library will let you use a shift instead of a division, but won't give you a constant time size function for Integers. You can easily get a logarithmic time size function from the shift. But did you see Data.Bits.bitsize

Re: [Haskell] Re: About Random Integer without IO

2004-11-12 Thread Dylan Thurston
On Fri, Nov 12, 2004 at 02:15:51PM +0100, Jerzy Karczmarczuk wrote: First, we don't care about 'real random' numbers, actually there are problems even with their definition. We need sequences which *behave* randomly, from the point of view of feasible tests, spectral/statistical;

Re: [Haskell] implicit parameters and the paper prepose.pdf

2004-11-20 Thread Dylan Thurston
On Sat, Nov 20, 2004 at 09:26:08AM -0800, John Velman wrote: In a recent message to this list (msg15410) Oleg referenced a paper comparing implicit parameters and implicit configurations with url http://www.eecs.harvard.edu/~ccshan/prepose/prepose.pdf . I'd like to read this, (and examine the

Re: [Haskell] Real life examples

2004-11-26 Thread Dylan Thurston
On Wed, Nov 24, 2004 at 01:34:31AM -0800, John Meacham wrote: Part of my current interest in #2 is that I have been experimenting with some full-program optimization algorithms which could perhaps give substantial gains but would pretty much obliterate any uses of the unsafePerformIO global

Re: [Haskell] How to zip folds: A library of fold transformers

2005-10-14 Thread Dylan Thurston
On Tue, Oct 11, 2005 at 05:25:24PM -0700, [EMAIL PROTECTED] wrote: First we define the representation of a list as a fold: newtype FR a = FR (forall ans. (a - ans - ans) - ans - ans) unFR (FR x) = x It has a rank-2 type. The defining equations are: if flst is a value of a type |FR a|,

Re: [Haskell] Re: (small) records proposal for Haskell '06

2006-01-03 Thread Dylan Thurston
On Tue, Jan 03, 2006 at 02:41:40PM -0800, Ashley Yakeley wrote: David Roundy wrote: On Mon, Jan 02, 2006 at 04:23:32PM -0800, Ashley Yakeley wrote: One open question (in my mind) would be whether we'd allow data Foo = FooInt { foo :: Int } | FooChar { foo :: Char } In the new system,

Re: Strange behaviour in implicit parameters

2001-04-26 Thread Dylan Thurston
checker seems a bit confused in this line: In the first argument of `fst', namely `env' since the argument of `fst' is `?env' in that version. Is this a different bug? --Dylan Thurston ___ Glasgow-haskell-bugs mailing list [EMAIL PROTECTED] http

-1796254192 `div` 357566600 == 5 ??

2002-06-27 Thread Dylan Thurston
. Loading package std ... linking ... done. Prelude -1796254192 `div` 357566600 5 Prelude Has this been fixed already? I checked, and the gmp library itself (Debian version 4.0.1-3) does not have this problem. Best, Dylan Thurston msg04894/pgp0.pgp Description: PGP signature

More on integer division

2002-06-29 Thread Dylan Thurston
On Fri, Jun 28, 2002 at 03:54:50PM -0400, Dylan Thurston wrote: On Fri, Jun 28, 2002 at 10:24:13AM +0100, Malcolm Wallace wrote: Yes,-5`div`2 == -(5`div`2) == -2 but (-5)`div`2 == -3 Ghc 5.02.2 has the infix priority wrong, and interprets the former as the latter. But more

Retraction

2002-06-29 Thread Dylan Thurston
On Sat, Jun 29, 2002 at 12:23:27PM -0400, Dylan Thurston wrote: After a looking a little more, there seem to be other problems (including errors in my proposed solution). I don't know where the code for quotRem is, but it is also buggy. For instance, Prelude 9 `quotRem` (-5) (-1,4

'-fno-implicit-prelude' doesn't use local fromRational

2004-07-11 Thread Dylan Thurston
The '-fno-implicit-prelude' flag uses the locally in scope fromInteger function for integer literals, but oddly always uses the global Prelude's fromRational function. Peace, Dylan signature.asc Description: Digital signature ___

Re: deriving...

2004-10-20 Thread Dylan Thurston
On Tue, Oct 19, 2004 at 08:08:49PM +0200, Andres Loeh wrote: Simon Peyton-Jones wrote: derive( Typeable (T a) ) But that means adding 'derive' as a keyword. Other possibilities: deriving( Typeable (T a) ) ... Any other ideas? instance Typeable (T a) deriving Why

Re: Double - CDouble, realToFrac doesn't work

2004-11-05 Thread Dylan Thurston
On Thu, Nov 04, 2004 at 08:32:52PM +0100, Sven Panne wrote: It's an old thread, but nothing has really happened yet, so I'd like to restate and expand the question: What should the behaviour of toRational, fromRational, and decodeFloat for NaN and +/-Infinity be? Even if the report is unclear

Re: [Haskell-cafe] Re: Double - CDouble, realToFrac doesn't work

2004-11-05 Thread Dylan Thurston
On Fri, Nov 05, 2004 at 02:53:01PM +, MR K P SCHUPKE wrote: My guess is because irrationals can't be represented on a discrete computer Well, call it arbitrary precision floating point then. Having built in Integer support, it does seem odd only having Float/Double/Rational... There are

Re: POLL: GC options

2001-08-06 Thread Dylan Thurston
because as Sigbjorn points out we don't ship the RtsFlags.h file which contains the definition of the flags structure :-( I'd like to be able to set these options with a flag to the compiler. --Dylan Thurston ___ Glasgow-haskell-users mailing list [EMAIL

Re: FFI

2002-01-12 Thread Dylan Thurston
situation: I want to interface to C code with several rather large structures, so plain FFI is not very attractive. I've started using C-Haskell, but am curious about other people's experiences.) --Dylan Thurston msg02917/pgp0.pgp Description: PGP signature

Re: Congrats to Mandrake

2002-02-20 Thread Dylan Thurston
debian user should just be able to say apt-get install ghc5 to get the latest package from the nearest mirror... Better: http://packages.debian.org/testing/devel/ghc5.html http://packages.debian.org/unstable/devel/ghc5.html --Dylan Thurston msg03123/pgp0.pgp Description: PGP signature

Re: Replacing the Prelude

2002-05-14 Thread Dylan Thurston
to implement it. --Dylan Thurston msg03485/pgp0.pgp Description: PGP signature

Re: replacing the Prelude (again)

2002-07-17 Thread Dylan Thurston
On Tue, Jul 16, 2002 at 04:02:44PM +1000, Bernard James POPE wrote: I would like to use do-notation in the transformed program, but have it refer to Prelude.Monad and not MyPrelude.Monad which is also in scope. Why do you have a MyPrelude.Monad (different from Prelude.Monad) if you don't want

Re: [Haskell] Dynamically loading wxhaskell?

2004-04-03 Thread Dylan Thurston
On Fri, Apr 02, 2004 at 01:59:08PM +0100, Simon Marlow wrote: Very strange. Is /usr/lib/libdl.so perhaps a symlink to a library that doesn't exist? That could happen if an upgrade had gone wrong, perhaps. Thanks, it was a dangling symlink due to my filesystem layout. Sorry for the stupidity.

Re: [Haskell] Dynamically loading wxhaskell?

2004-04-13 Thread Dylan Thurston
On Tue, Apr 13, 2004 at 03:53:31PM +0100, Simon Marlow wrote: I tried stripping /usr/lib/libwx_gtk-2.4.so.0.1.1 and libwxc-0.6.so, and GHCi was still able to load the wx package successfully. In fact, libwx_gtk appeared to be already stripped. What error messages do you get, specifically?

Re: [Haskell] Dynamically loading wxhaskell?

2004-04-14 Thread Dylan Thurston
On Wed, Apr 14, 2004 at 09:37:02AM +0100, Simon Marlow wrote: ... That symbol looks suspiciously like it comes from the separate OpenGL parts of WX, which reside in a separate library (/usr/lib/libwx_gtk_gl-2.4.so here). On my system, libwxc has an explicit dependency on libwx_gtk_gl, because

Alternatives to . for composition

2006-03-25 Thread Dylan Thurston
= APL jot 00B0 degree sign 25E6 white bullet I don't think any other Unicode character should be considered. (Is this the approved way to send minor updates like this?) Peace, Dylan Thurston signature.asc Description: Digital signature

Re: [Haskell-cafe] Features of Haskell

2006-06-04 Thread Dylan Thurston
he managed to explain very effectively what made Haskell ^^ she Peace, Dylan Thurston signature.asc Description: Digital signature ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell-cafe] Re: mathematical notation and functional programming

2005-02-04 Thread Dylan Thurston
(Resurrecting a somewhat old thread...) On Fri, Jan 28, 2005 at 08:16:59PM +0100, Henning Thielemann wrote: On Fri, 28 Jan 2005, Chung-chieh Shan wrote: But I would hesitate with some of your examples, because they may simply illustrate that mathematical notation is a language with side

Re: [Haskell-cafe] Re: mathematical notation and functional programming

2005-02-05 Thread Dylan Thurston
On Fri, Feb 04, 2005 at 03:08:51PM +0100, Henning Thielemann wrote: On Thu, 3 Feb 2005, Dylan Thurston wrote: On Fri, Jan 28, 2005 at 08:16:59PM +0100, Henning Thielemann wrote: O(n) which should be O(\n - n) (a remark by Simon Thompson in The Craft

Re: [Haskell-cafe] Data types and Haskell classes

2005-05-18 Thread Dylan Thurston
On Tue, May 17, 2005 at 01:13:17PM +0200, Jens Blanck wrote: How would I introduce number classes that are extended with plus and minus infinity? I'd like to have polymorphism over these new classes, something like a signature f :: (Real a, Extended a b) = b - b which clearly

Re: [Haskell-cafe] Project postmortem II /Haskell vs. Erlang/

2006-01-03 Thread Dylan Thurston
On Sun, Jan 01, 2006 at 11:12:31PM +, Joel Reymont wrote: Simon, Please see this post for an extended reply: http://wagerlabs.com/articles/2006/01/01/haskell-vs-erlang-reloaded Looking at this code, I wonder if there are better ways to express what you really want using static typing.

Re: [Haskell-cafe] Progress on shootout entries

2006-01-03 Thread Dylan Thurston
On Wed, Jan 04, 2006 at 03:02:29AM +0100, Sebastian Sylvan wrote: I took a stab at the rev-comp one due to boredom. It's not a space leak, believe it or not, it's *by design*... My god, I think someone is consciously trying to sabotage Haskell's reputation! Instead of reading input

Re: [Haskell-cafe] Re: Positive integers

2006-03-27 Thread Dylan Thurston
On Mon, Mar 27, 2006 at 05:02:20AM -0800, John Meacham wrote: well, in interfaces you are going to end up with some specific class or another concretely mentioned in your type signatures, which means you can't interact with code that only knows about the alternate class. like genericLength

Re: [Haskell-cafe] Proposal for restructuring Number classes

2006-04-17 Thread Dylan Thurston
linear algebra library recently posted to the Haskell list.) Peace, Dylan Thurston signature.asc Description: Digital signature ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: [Haskell-cafe] Re: Proposal for restructuring Number classes

2006-04-17 Thread Dylan Thurston
with the Kiselyov-Shan approach to dependent types? Does it look too bizarre? http://okmij.org/ftp/Haskell/types.html#Prepose http://okmij.org/ftp/Haskell/number-parameterized-types.html Peace, Dylan Thurston signature.asc Description: Digital signature

(no subject)

2001-02-07 Thread Dylan Thurston
___ Haskell-Cafe mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell-cafe

Re: Revamping the numeric classes

2001-02-07 Thread Dylan Thurston
a==a may be Bottom, so what's the problem? It would be a problem, though, to have to explain to a beginner why they can't print the result of a computation. Why doesn't your argument show that all types should by instances of Eq and Show? Why are numeric types special? Best, Dylan Thurston

  1   2   >