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

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] 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] Nice way to calculate character frequency in a string

2005-10-25 Thread Lennart Augustsson
Sebastian Sylvan wrote: Also, you may use STArrays (I think they come in unboxed as well) for stateful code, which may be even faster (unless accumArray does some neat trick to make it O(m) where m is the number of index/value pairs). The whole idea with having accumArray as part of the Array

Re: [Haskell-cafe] newtype is superfluous

2005-10-15 Thread Lennart Augustsson
Wolfgang Jeltsch wrote: Am Samstag, 15. Oktober 2005 08:31 schrieb Bulat Ziganshin: Hello Haskell, number of type definition statements in Haskell (data, type, newtype) is a bit too large. at least, newtype definition seems to be superfluous - it can be replaced by the same `data`

Re: [Haskell] strictness of putChar: report incomplete?

2005-10-06 Thread Lennart Augustsson
Simon Marlow wrote: I agree with you. And that is how it used to be, but then some people didn't think that was convenient enough so now we are stuck with a seq that (IMHO) stinks. :) Having a seq that works on anything is occasionally very useful for fixing space leaks, and the type class

Re: [Haskell] strictness of putChar: report incomplete?

2005-10-05 Thread Lennart Augustsson
Wolfgang Jeltsch wrote: Am Mittwoch, 5. Oktober 2005 16:22 schrieb Simon Marlow: [...] Also, GHC's optimiser currently treats (_|_ :: IO a) and (do _|_; return ()) as interchangeable, which is naughty, and people have occasionally noticed, but the benefits can sometimes be huge. It is

Re: [Haskell] Literal for Infinity

2005-10-02 Thread Lennart Augustsson
Not all FP representations have infinity, and even if they do, they might only have one infinity. -- Lennart Frederik Eaton wrote: I've previously mentioned that I would like to see an 'instance Bounded Double' etc., as part of the standard, which would use 1/0 for maxBound, or the

Re: [Haskell] Literal for Infinity

2005-09-29 Thread Lennart Augustsson
The RealFloat class has a number of methods for testing various properties of a FP number: isNaN :: a - Bool isInfinite :: a - Bool isDenormalized :: a - Bool isNegativeZero :: a - Bool isIEEE :: a - Bool If you really want to create an Infinity, I suggest 1/0, but not all FP formats

Re: [Haskell-cafe] Trapped by the Monads

2005-09-20 Thread Lennart Augustsson
Mark Carter wrote: The typical example in C is: mem = malloc(1024) Malloc returns 0 to indicate that memory cannot be allocated, or a memory address if it can. The variable mem is a so-called hybrid variable; it crunches together 2 different concepts: a boolean value (could I allocate

Re: [Haskell-cafe] Trapped by the Monads

2005-09-20 Thread Lennart Augustsson
a pointer without checking for 0, and extracting the Maybe value without handling Nothing, apart from that it leads to undefined behavior in C which in fact isn't really a point against hybrid variables. On 9/20/05, Lennart Augustsson [EMAIL PROTECTED] wrote: Mark Carter wrote: The typical

Re: [Haskell-cafe] Re: [Haskell] pros and cons of static typing and side effects ?

2005-08-16 Thread Lennart Augustsson
Keean Schupke wrote: Other things we can do ... with dependant types we can ask the compiler to prove the correctness of sorting algorithms. If we define an ordered list tgo be one where each element must be larger than the preceding one: data OrderedIntList = Cons (a::Int)

Re: [Haskell] Haskell SOE Question

2005-07-27 Thread Lennart Augustsson
But who said you should remove the import of word32ToInt? It was only fromIntegral that was discussed. -- Lennart Alex Edelsburg wrote: Thanks for your suggestion. --import Word (fromIntegral) --import Word (word32ToInt) I removed both import statements from the code and tried to run

Re: [Haskell] offside rule question

2005-07-13 Thread Lennart Augustsson
it with {}. Thanks, Frederik On Thu, Jul 14, 2005 at 02:42:53AM +0200, Lennart Augustsson wrote: That's how it is defined in the Haskell definition. But there is a reason. The offside rule (or whatever yoy want to call it) is there to give visual cues. If you were allowed to override these easily just

Re: [Haskell-cafe] matrix computations based on the GSL

2005-07-07 Thread Lennart Augustsson
David Roundy wrote: The issue is that Haskell (as far as I understand, and noone has suggested anything to the contrary) doesn't have a sufficiently powerful type system to represent matrices or vectors in a statically typed way. It would be wonderful if we could represent matrix multiplication

Re: [Haskell-cafe] type inference and named fields

2005-06-24 Thread Lennart Augustsson
Jonathan Cast wrote: No type theory (that I know of) goes beyond System F in accepting anything like foo. So, given the current state of the art, foo is unconditionally ill-typed. That could change if someone comes up with a /consistent/ type theory that accepts foo, but foo is

Re: [Haskell] Dynamic binding

2005-06-23 Thread Lennart Augustsson
Andrew Ward wrote: Hi All, In Simon Thompson's The Craft of Functional Programming Second Edition, page 226, it is mentioned that Laufer (1996) describes a Haskell extension to allow dynamic binding. I was wondering if this has been implemented as an extension in any of the haskell compilers,

Re: [Haskell] Dynamic binding

2005-06-23 Thread Lennart Augustsson
in on b) but I maintain a) and I really miss extensible datatypes :-) Ralf (doing too much C# these days I guess) -Original Message- From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On Behalf Of Lennart Augustsson Sent: Thursday, June 23, 2005 7:30 AM To: Andrew Ward Cc: haskell

Re: [Haskell-cafe] type inference and named fields

2005-06-23 Thread Lennart Augustsson
A somewhat similar problem exists even without fields: foo :: Either a b - Either () b foo (Left _) = Left () foo x@(Right _) = x Since Haskell type checking doesn't use the information gained by pattern matching to refine types we just have to accept that some perfectly safe programs don't

Re: [Haskell-cafe] type inference and named fields

2005-06-23 Thread Lennart Augustsson
. I sort-of expected that the extension to pattern matching would follow. Or is that a nice paper waiting to be written? Jacques Lennart Augustsson [EMAIL PROTECTED] wrote: A somewhat similar problem exists even without fields: foo :: Either a b - Either () b foo (Left _) = Left () foo x

Re: [Haskell-cafe] type inference and named fields

2005-06-23 Thread Lennart Augustsson
Jonathan Cast wrote: Lennart Augustsson [EMAIL PROTECTED] wrote: A somewhat similar problem exists even without fields: foo :: Either a b - Either () b foo (Left _) = Left () foo x@(Right _) = x Since Haskell type checking doesn't use the information gained by pattern matching to refine

Re: [Haskell-cafe] (small) code review request

2005-06-16 Thread Lennart Augustsson
Radu Grigore wrote: Anyway, I was wondering if the O(n) space and O(n^2) time solution can be implemented in Haskell. Another way to ask this. Consider the classic fibonacci example. Can one compute the n-th fibonacci number in O(n) time and O(1) space, i.e. remember only the last two values

Re: unsafeness of unsafeInterleaveIO

2005-06-10 Thread Lennart Augustsson
You pick. :) It can break referential transparency. It can break type safety. -- Lennart Andre Pang wrote: G'day all, Just looking at the documentation for System.IO.unsafeInterleaveIO, what exactly is unsafe about it? ___

Re: unsafeness of unsafeInterleaveIO

2005-06-10 Thread Lennart Augustsson
Andre Pang wrote: On 10/06/2005, at 11:16 AM, Remi Turk wrote: Are you sure you're not talking about unsafePerformIO? System.IO.Unsafe.unsafePerformIO:: IO a - a System.IO.Unsafe.unsafeInterleaveIO :: IO a - IO a [written to Lennert Augustsson]: yes, I think you misread

Re: On Eq, was Re: [Haskell-cafe] When to use fancy types [Re: NumberTheory library]

2005-05-14 Thread Lennart Augustsson
Jacques Carette wrote: Anyone who thinks that +0 = -0 has never wrestled with a branch cut (and lost...). Such people have the nasty habit of also thinking that ALL functions are continuous! You might think they were constructivists or something. Why would a constructivist think that all

Re: [Haskell-cafe] When to use fancy types [Re: NumberTheory library]

2005-05-12 Thread Lennart Augustsson
Thank you for saying what I was too lazy to say myself. :) -- Lennart Jan-Willem Maessen wrote: On May 10, 2005, at 4:14 AM, Bo Herlin wrote: Well, part of what I was doing was experimenting with what a library like this should look like, even more than what it should do. For some

Re: [Haskell-cafe] resolving missing class instances @ compile time

2005-05-12 Thread Lennart Augustsson
Greg Buchholz wrote: Samuel Bronson wrote: The former may not be hard, but the latter would require functions with typeclass constraints on their types to be annotated in the interface file with what typeclass methods they called. Does that sound hard yet? Compared to writing the rest of the

Re: [Haskell-cafe] Linux device drivers

2005-03-22 Thread Lennart Augustsson
But there are plenty of minor variations on how to program and initiate DMA for different devices. -- Lennart Keean Schupke wrote: Actually with PCI chipsets, implementing a generic BusMaster DMA driver is not too hard, assuming you already have interrupts handled (and you don't want

Re: [Haskell-cafe] Linux device drivers

2005-03-22 Thread Lennart Augustsson
chipset to chipset. Keean. Lennart Augustsson wrote: But there are plenty of minor variations on how to program and initiate DMA for different devices. ___ Haskell-Cafe mailing list Haskell-Cafe@haskell.org http://www.haskell.org/mailman/listinfo/haskell

Re: [Haskell-cafe] Linux device drivers

2005-03-22 Thread Lennart Augustsson
Keean Schupke wrote: Have a look at the linux kernel IDE drivers, look for Generic IDE Chipset support That's the part I missed, you were talking about IDE chips. Yes, they have many similarities. You can probably run many of them in one of the slower modes with a common driver. But even these

Re: [Haskell] instance Bounded Double

2005-03-13 Thread Lennart Augustsson
seems like another reason to define a Bounded instance for Double. That way users could call 'maxBound' and 'minBound' rather than 1/0 and -(1/0)... Frederik On Fri, Mar 11, 2005 at 11:10:33AM +0100, Lennart Augustsson wrote: Haskell does not guarantee that 1/0 is well defined, nor that -(1/0

Re: [Haskell] instance Bounded Double

2005-03-13 Thread Lennart Augustsson
that portability seems like another reason to define a Bounded instance for Double. That way users could call 'maxBound' and 'minBound' rather than 1/0 and -(1/0)... Frederik On Fri, Mar 11, 2005 at 11:10:33AM +0100, Lennart Augustsson wrote: Haskell does not guarantee that 1/0 is well defined, nor that -(1

Re: [Haskell] instance Bounded Double

2005-03-11 Thread Lennart Augustsson
Haskell does not guarantee that 1/0 is well defined, nor that -(1/0) is different from 1/0. While the former is true for IEEE floating point numbers, the latter is only true when using affine infinities. -- Lennart Frederik Eaton wrote: Shouldn't Double, Float, etc. be instances of

Re: [Haskell-cafe] Point-free style

2005-02-14 Thread Lennart Augustsson
Daniel Fischer wrote: And could one define \f g h x y - f (g x) (h y) point-free? Any definition can be made point free if you have a complete combinator base at your disposal, e.g., S and K. Haskell has K (called const), but lacks S. S could be defined as spread f g x = f x (g x) Given that

Re: [Haskell-cafe] Point-free style

2005-02-14 Thread Lennart Augustsson
Remi Turk wrote: import Control.Monad.Reader k :: a - b - a k = return s :: (a - r - b) - (a - r) - a - b s = flip (=) . flip Greetings, Remi Oh, a little bit of cheating. ;) But neat. It can be done without importing anything. (Except the implicit Prelude import, of course.) -- Lennart

Re: [Haskell-cafe] Point-free style

2005-02-14 Thread Lennart Augustsson
Joe Fasel argued for the inclusion of S or W in the prelude on the grounds that a complete combinator base would be neat. But the majority of the Haskell committee didn't buy that. -- Lennart Peter G. Hancock wrote: Lennart Augustsson wrote (on Mon, 14 Feb 2005 at 14:55): Any

Re: [Haskell] Newbie : How come that cyclic recursive lists are efficient ?

2005-01-24 Thread Lennart Augustsson
It doesn't have to be a top level definition, it works anyway. -- Lennart Bruno Abdon wrote: 'hamming', in your code, is a top-level definition. When used three times inside its own definition, it's the same variable being used three times. You don't recompute a variable value in order to

Re: [Haskell] Re: Never GADT Function?

2005-01-08 Thread Lennart Augustsson
Well, this compiles: data T a where BoolT :: T Bool IntT :: T Int neverT' :: T a - x neverT' BoolT = error Bool neverT' IntT = error Int neverT :: T Char - x neverT = neverT' But it uses error for the unreachable cases, maybe not what you want. -- Lennart Ashley Yakeley wrote: In

Re: [Haskell-cafe] Hugs vs GHC (again) was: Re: Some randomnewbiequestions

2005-01-07 Thread Lennart Augustsson
Simon Marlow wrote: Many years ago, hbc claimed to be the only compiler with support for this. What encoding(s) did hbc allow in source files? The docs only mention unicode characters inside character string literals. The Java encoding, i.e., \u. -- Lennart

Re: [Haskell-cafe] Hugs vs GHC (again) was: Re: Some randomnewbiequestions

2005-01-07 Thread Lennart Augustsson
Malcolm Wallace wrote: Lennart writes: What encoding(s) did hbc allow in source files? The docs only mention unicode characters inside character string literals. The Java encoding, i.e., \u. Well, in that case, nhc98 also supports Unicode in source files, identically to hbc. Well, you have

Re: [Haskell-cafe] coercion to Int

2004-12-31 Thread Lennart Augustsson
fnK_ :: Int - Int fnK_ = round . sqrt . fromIntegral james pentland wrote: what coercion can i use to get the below program to compile? i see class (Real a, Fractional a) = RealFrac a where round :: (Integral b) = a - b and class (Fractional a) = Floating a where sqrt

Re: [Haskell-cafe] Re: Non-technical Haskell question

2004-12-07 Thread Lennart Augustsson
Simon Marlow wrote: Dynamic linking is (almost) a separate issue. GHC 6.4 will have some support for dynamic linking in the native code generator thanks to Wolfgang Thaller, but it needs someone to push it the final mile on x86/Linux and Windows. Dynamically linked libraries will work (albeit

Re: [Haskell-cafe] Re: Non-technical Haskell question

2004-12-07 Thread Lennart Augustsson
John Goerzen wrote: On Tue, Dec 07, 2004 at 12:43:27PM +0100, Lennart Augustsson wrote: slightly slower than statically linked ones), but you still have the versioning issue. Yay! :) Dynamically linked libraries are slower than statically linked ones in just about every implementation I know

Re: [Haskell-cafe] Non-technical Haskell question

2004-12-06 Thread Lennart Augustsson
[EMAIL PROTECTED] wrote: The original observation was that the compiler seems archaic. When asked, I gave some general comments. What I should have just said was that it was to much like a C compiler. Which, no matter how neat you think it is, is archaic. Archaic doesn't mean that it's bad. :)

Re: [Haskell-cafe] Re: Non-technical Haskell question

2004-12-06 Thread Lennart Augustsson
Ketil Malde wrote: John Goerzen [EMAIL PROTECTED] writes: sensibly share libraries between apps. Anyway, disc is cheap. Memory not so much, though. One advantage of having something in .so form is that every instance of every application that uses it shares the same in-memory image of the

Re: [Haskell-cafe] Re: ACIO versus Execution Contexts

2004-12-01 Thread Lennart Augustsson
Adrian Hey wrote: On Tuesday 30 Nov 2004 3:02 pm, Lennart Augustsson wrote: I reiterate: not even device drivers written in C use TWIs. (Well, at least not quality drivers. :)) A finite pool of N devices is still a unique resource. Ultimately you have to contain the problem locally

Re: [Haskell-cafe] ACIO versus Execution Contexts

2004-11-30 Thread Lennart Augustsson
Keean Schupke wrote: Look at how Linux scans the hardware at boot time and initialises a driver for each device it finds... that means that each driver is parameterised by the IO address of the device, and can be initialised multiple times. When an OS boots it runs an initialisation routine (the

Re: [Haskell-cafe] Re: Efficient or predictable Ord for Typeable

2004-11-30 Thread Lennart Augustsson
George Russell wrote: Simon Peyton-Jones wrote: The trouble is that *any* function can now deliver unpredictable results. Can I rely on the fact that foo :: Int - Int will always give the same answer given the same input. Not any more. Yes, I see what you mean. I think the strongest

[Fwd: Re: [Haskell-cafe] Re: ACIO versus Execution Contexts]

2004-11-30 Thread Lennart Augustsson
---BeginMessage--- Adrian Hey wrote: Keean and Lennart are just hiding the problem in a hypothetical operating system which is simply assumed to be correct (it just doesn't do any of the dangerous things that might otherwise be done). Well, if think I'm not reading your postings then I think I

Re: [Haskell] Real life examples

2004-11-28 Thread Lennart Augustsson
But surely any device driver is parametrized on the exact IO addresses? How would you be able to handle multiple devices otherwise? Adrian Hey wrote: On Friday 26 Nov 2004 11:39 am, Keean Schupke wrote: Adrian Hey wrote: Well it can be written in Haskell, but not using a module that was

Re: [Haskell] Better Exception Handling

2004-11-26 Thread Lennart Augustsson
Tomasz Zielonka wrote: On Thu, Nov 25, 2004 at 07:52:43PM +0100, Lennart Augustsson wrote: As I'm sure you have gathered from all the answers you can't have the latter and keep Haskell pure. But there is an interesting alternative (at least theoretically). You could have a function like

[Haskell-cafe] Re: [Haskell] A puzzle and an annoying feature

2004-11-26 Thread Lennart Augustsson
Martin Sulzmann wrote: [Discussion moved from Haskell to Haskell-Cafe] Hi, Regarding - lazy overlap resolution aka unique instances Well, if there's only instance which is not exported, then you can use functional dependencies. Assume class C a instance ... = C t Internally, use class C a | - a

Re: [Haskell] Real life examples

2004-11-25 Thread Lennart Augustsson
Ben Rudiak-Gould wrote: Lennart Augustsson wrote: What do you mean when you say the interface is pure? If your module is really pure then there should be an implemenation of it (which could have really bad complexity) with the same observable behaviour that uses only pure Haskell

Re: [Haskell] A puzzle and an annoying feature

2004-11-25 Thread Lennart Augustsson
[EMAIL PROTECTED] wrote: G'day all. Quoting Lennart Augustsson [EMAIL PROTECTED]: Here is a small puzzle. You can understand this one because the closed world hypothesis doesn't apply to type context inference. I have no problem understanding the technical reason for this. But I now think it's

Re: [Haskell] Real life examples

2004-11-25 Thread Lennart Augustsson
I don't necessarily agree that you can do this trick in all implementations of Dynamic and Typable. You're relying on more things than the interface to Dynamic promises. Your fromDynamic could very well return Nothing. And should! But that doesn't matter. The unsafeCast function doesn't really

Re: [Haskell] Real life examples

2004-11-25 Thread Lennart Augustsson
] [mailto:[EMAIL PROTECTED] On Behalf Of Marcin 'Qrczak' Kowalczyk Sent: den 25 november 2004 11:49 To: [EMAIL PROTECTED] Subject: Re: [Haskell] Real life examples Lennart Augustsson [EMAIL PROTECTED] writes: An easy way to prove it is to provide an equivalent implementation that uses only pure functions

Re: [Haskell] A puzzle and an annoying feature

2004-11-25 Thread Lennart Augustsson
Daan Leijen wrote: Keean Schupke wrote: No, closed classes are different, here we are talking about lazy overlap resolution, so if at _call_ time only one instance fits we choose it. Closing a class is different. A closed class directive however is an explicit specification that makes the

Re: [Haskell] A puzzle and an annoying feature

2004-11-25 Thread Lennart Augustsson
Of course it can. I might do it myself. :) -- Lennart Keean Schupke wrote: I have already asked Simon PJ if this can be implemented in GHC... So if more people ask for it, it might get done! Keean Lennart Augustsson wrote: Here is a small puzzle. -- The following generates a type

Re: [Haskell] A puzzle and an annoying feature

2004-11-25 Thread Lennart Augustsson
Graham Klyne wrote: I have a concern with this, if I understand the issue correctly. Suppose I have a source module that compiles and runs correctly. Now suppose I add a restricted (selective) import statement to the file, explicitly introducing a name that I know does not clash with anything in

Re: [Haskell] Better Exception Handling

2004-11-25 Thread Lennart Augustsson
John Goerzen wrote: So why do we have: catchJust :: (Exception - Maybe b) - IO a - (b - IO a) - IO a instead of: catchJust :: (Exception - Maybe b) - (c - a) - c - (b - a) - a As I'm sure you have gathered from all the answers you can't have the latter and keep Haskell pure. But there is an

Re: [Haskell] Better Exception Handling

2004-11-25 Thread Lennart Augustsson
Tomasz Zielonka wrote: On Thu, Nov 25, 2004 at 07:52:43PM +0100, Lennart Augustsson wrote: As I'm sure you have gathered from all the answers you can't have the latter and keep Haskell pure. But there is an interesting alternative (at least theoretically). You could have a function like

Re: [Haskell] Better Exception Handling

2004-11-25 Thread Lennart Augustsson
Jules Bean wrote: By the same token, you can just stick the function strangeReadFile :: FilePath - String into the language. As long as it is memoized, always returning the same value, it doesn't break beta-reduction. I call it 'strange' because the time that the file is actually read is not

Re: [Haskell] A puzzle and an annoying feature

2004-11-25 Thread Lennart Augustsson
Daan Leijen wrote: You are right, I feel like that too: one should expect that the type checker can figure this out, and perhaps it is even really useful. On the other hand, suppose you decide later to export the class, and suddenly your code would no longer type check. The fact that adding an

Re: [Haskell] A puzzle and an annoying feature

2004-11-25 Thread Lennart Augustsson
Keean Schupke wrote: Daan Leijen wrote: You are right, I feel like that too: one should expect that the type checker can figure this out, and perhaps it is even really useful. On the other hand, suppose you decide later to export the class, and suddenly your code would no longer type check. I

Re: [Haskell] Real life examples

2004-11-24 Thread Lennart Augustsson
Tomasz Zielonka wrote: On Tue, Nov 23, 2004 at 08:50:45PM -0800, John Meacham wrote: Atom.hs from ginsu.. This is perhaps the best example, and an incredibly useful piece of code for anyone struggling with space problems out there. it provides data Atom = ... (abstract) instance Ord Atom

Re: Top Level TWI's again was Re: [Haskell] Re: Parameterized Show

2004-11-24 Thread Lennart Augustsson
Adrian Hey wrote: On Tuesday 23 Nov 2004 9:39 am, Lennart Augustsson wrote: I find it hard to argue these things in the abstract. Could you post us a (simplified) signature for a module where you are using top level variables? Maybe that way I can be convinced that you need them. Or vice versa

Re: Top Level TWI's again was Re: [Haskell] Re: Parameterized Show

2004-11-24 Thread Lennart Augustsson
Adrian Hey wrote: On Tuesday 23 Nov 2004 9:29 am, Keean Schupke wrote: myDriver :: (Chan in,Chan out) - State - IO State myDriver (in,out) state = do -- read commands from in -- process commands -- reply on out myDriver (in,out) new_state How does this solve the

Re: [Haskell] Real life examples

2004-11-24 Thread Lennart Augustsson
George Russell wrote: I think their disadvantages are overstated. Glasgow Haskell uses them lots, And I bet the implementors wish they hadn't used them as much. ;) Now we have some weird division of flags into static and dynamic, for instance. Global (top level) variables can be very

Re: [Haskell] Real life examples

2004-11-24 Thread Lennart Augustsson
Ben Rudiak-Gould wrote: Yes it does. :-) If each Haskell environment ships with a correct implementation of the library, then its interface is the only part that matters. If the unsafePerformIO hack doesn't work in your new Haskell compiler, you can replace it with some other magic that does

Re: Top Level TWI's again was Re: [Haskell] Re: Parameterized Show

2004-11-23 Thread Lennart Augustsson
Adrian Hey wrote: As for openDevice, if a device should only allow a single open I would assume this is part of the device driver in the operating system? (I know this is shifting blame. But I think it shifts it to where it belongs. In the OS there will be an open flag per device.) IOW there is

Re: [Haskell] Global Variables and IO initializers

2004-11-23 Thread Lennart Augustsson
George Russell wrote: (3) It needs no extensions to the Haskell language, and only fairly standard hierarchical libraries like Data.IORef. It uses unsafePerformIO which is very much an extension to Haskell. :) -- Lennart ___ Haskell mailing list

Re: [Haskell] Re: Global Variables and IO initializers

2004-11-23 Thread Lennart Augustsson
[EMAIL PROTECTED] wrote: No. I mean by the Haskell language what is described in the Haskell 98 Report. unsafePerformIO is not part of the language, it is a value defined by one of the standard hierarchical libraries. unsafePerformIO is part of the FFI addendum to the H98 report. So I think

Re: [Haskell] Re: Parameterized Show

2004-11-16 Thread Lennart Augustsson
George Russell wrote: Since it hasn't been mentioned yet I should also point people once again to Functional Pearl: Implicit Configurations by Oleg and Chung-chieh Shan, which ingeniously uses polymorphic recursion to construct type class instances at run time. If there's a safe and sane way to

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

2004-11-08 Thread Lennart Augustsson
Henning Thielemann wrote: On Fri, 5 Nov 2004, Robert Dockins wrote: What IEEE has done is shoehorned in some values that aren't really numbers into their representation (NaN certainly; one could make a convincing argument that +Inf and -Inf aren't numbers). I wonder why Infinity has a sign in

Re: [Haskell] Re: Global Variables and IO initializers

2004-11-08 Thread Lennart Augustsson
Adrian Hey wrote: Why are top level IORefs any worse than other IORefs (for example)? Because global variables are just BAD. They have been considered bad a long time, it's not a Haskell thing. If you really grok the functional way of doing things there should be *very*, *very* few times you need

Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-08 Thread Lennart Augustsson
Adrian Hey wrote: 4- They already exist (stdin,stout,stderr) and I don't recall anybody ever complaining about this. stdin, stdout, and stderr are not global variables. They are just handles. One possible implementation of handles is as an Int. So stdin is no more a global variable than 0.

Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-08 Thread Lennart Augustsson
Keean Schupke wrote: Adrian Hey wrote: The first step to solving a problem is to at least recognise that it exists. What is bizarre is that so many folk seem to be in denial over this. Perhaps you would like to show me your solution to the oneShot problem. Why are you unable to give a concrete

Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-08 Thread Lennart Augustsson
Jules Bean wrote: Yes... a lot of the example we have seen here are 'just' handles. newIORef creates handles. Something many programmers would like is the ability to create fresh handles at the toplevel... Yes, I hear what they want. That doesn't mean I think it's a good idea. Top level

[Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-08 Thread Lennart Augustsson
Adrian Hey wrote: Why are top level IORefs any worse than other IORefs (for example)? Because global variables are just BAD. They have been considered bad a long time, it's not a Haskell thing. If you really grok the functional way of doing things there should be *very*, *very* few times you need

Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-08 Thread Lennart Augustsson
Adrian Hey wrote: 4- They already exist (stdin,stout,stderr) and I don't recall anybody ever complaining about this. stdin, stdout, and stderr are not global variables. They are just handles. One possible implementation of handles is as an Int. So stdin is no more a global variable than 0.

Re: [Haskell-cafe] Re: [Haskell] Re: Global Variables and IO initializers

2004-11-08 Thread Lennart Augustsson
Keean Schupke wrote: Adrian Hey wrote: The first step to solving a problem is to at least recognise that it exists. What is bizarre is that so many folk seem to be in denial over this. Perhaps you would like to show me your solution to the oneShot problem. Why are you unable to give a concrete

Re: constant space `minimum'

2004-09-30 Thread Lennart Augustsson
On Thu, 30 Sep 2004, Serge D. Mechveliani wrote: I thought naively that the Report function definitions can be treated more flexy, varied by implementations, with preserving some declared main properties. The definitions in the Report are to be treated as specifications. Any implementation should

Re: [Haskell] Correct interpretation of the curry-howard isomorphism

2004-04-23 Thread Lennart Augustsson
JP Bernardy wrote: I'd say, check what any primitive 'proves' before using it. Besides that, calling other functions is ok. Except for general recursion. coerce :: a - b coerce = coerce -- Lennart ___ Haskell mailing list [EMAIL PROTECTED]

Re: optimization question

2004-02-23 Thread Lennart Augustsson
Simon Peyton-Jones wrote: generate case expressions when there is more than one string in the list, otherwise use an equality test Oh, you mean like hbc does? ;-) Sorry, couldn't resist. -- Lennart ___ Glasgow-haskell-users mailing list

Re: [Haskell] Re: Data.Set whishes

2004-02-20 Thread Lennart Augustsson
I think it's because of tradition. Originally Haskell didn't have qualified names, only renaming. (Which, IMHO, was a wrong decision in the original Haskell design.) -- Lennart Koen Claessen wrote: | http://www.haskell.org/hierarchical-modules/libraries/library-design.html I have always

Re: getting the path to the executing program

2004-01-08 Thread Lennart Augustsson
Hal Daume III wrote: is there a function, related to getProgName, which returns the (absolute) path to the current program? Well, the absolute path name is not necessarily unique, nor is it guaranteed to exist. :) -- Lennart ___ Haskell mailing list

Re: no continuations

2003-12-30 Thread Lennart Augustsson
I'm not sure what your question means. You can make your own continuations, so in that sense Haskell has them. But perhaps you're asking why Haskell lacks something like call/cc in Scheme which allows you to grab the current continuation? This doesn't play very well with graph reduction (which

Re: Haskell naming conventions

2003-12-25 Thread Lennart Augustsson
Sean L. Palmer wrote: class Eq a where (==) :: a - a - Bool That actually declares a /type class/, not a class. So why the use of the keyword class? Is it done merely to confuse C++ and Java programmers? The concept of type class in Haskell apparently roughly corresponds to the

Re: Why are strings linked lists?

2003-11-28 Thread Lennart Augustsson
Glynn Clements wrote: What Unicode support? Simply claiming that values of type Char are Unicode characters doesn't make it so. Just because some implementations lack toUpper etc. doesn't mean they all do. Hbc has had those implemented for maybe 10 years. -- Lennart

Re: a type question

2003-11-26 Thread Lennart Augustsson
rui yang wrote: Suppose I have a function: funcmap :: a-b-c can I use type synonyms to describe a new type like this: Type Funcmap = a-bc ? First, it's 'type' not 'Type'. Second, you want '-' not ''. Third, all type variables in the RHS must be on the LHS. So, we get type Funcmap a b c =

Re: Enum on Float/Double

2003-10-22 Thread Lennart Augustsson
float? On Tue, 21 Oct 2003, Lennart Augustsson wrote: So this has been a while, but i think that decodeFloat, incrementing the mantissa, encodeFloat might work. But then again, it might not. :) -- Lennart Hal Daume III wrote: My preference would be for succ (+-0) to return the smallest positive

Re: Enum on Float/Double

2003-10-21 Thread Lennart Augustsson
So this has been a while, but i think that decodeFloat, incrementing the mantissa, encodeFloat might work. But then again, it might not. :) -- Lennart Hal Daume III wrote: My preference would be for succ (+-0) to return the smallest positive real, since then you could define succ x to be the

Re: IO behaves oddly if used nested

2003-10-02 Thread Lennart Augustsson
Alastair Reid wrote: Another question with a trivial answer, what is the result of: main :: IO (IO ()) main = return (putStr Hello World!) It is a computation which, if executed, will print Hello World Clearly it also shows the relation between IO and chosen evaluation strategy. This

Re: IO behaves oddly if used nested

2003-10-02 Thread Lennart Augustsson
Derek Elkins wrote: If I'm not mistaken, the Report restricts main's type to be, at least, IO a. Anyways, it's perfectly sensible to return anything. The RTS simply discards it. The above example as an entire program is an IO action that returns an IO action that is discarded by the RTS. You're

Re: loop through the list...

2003-08-10 Thread Lennart Augustsson
This really sounds a lot like home work. :) -- Lennart Fredrik Petersson wrote: hi again... :) Ok assume i got this list of tuples [(10,1),(20,2),(30,3)] where i in (i,j) is a index, i want to go through the list and add a number witch matches the best index. Like 18 should give me

Re: How to modify GHC internals?

2003-07-19 Thread Lennart Augustsson
Aim To guarantee security of a Haskell program so it can be used as an applet. /Aim Method Over-ride GHC's code generator to produce an assembly language that I specify. Also disable program access to system calls and foreign functions, except for a single trusted library that I specify. /Method

Re: ANNOUNCE: 0th International Obfuscated Haskell Code Contest

2003-02-14 Thread Lennart Augustsson
Shae Matijs Erisson wrote: The following message is a courtesy copy of an article that has been posted to comp.lang.functional as well. In the spirit of http://ioccc.org/ Bring us your poor, weary, downtrodden, and unreadable source code. Come to the 0th INTERNATIONAL OBFUSCATED HASKELL

Re: buffering woes

2003-02-05 Thread Lennart Augustsson
Malcolm Wallace wrote: Hal Daume III [EMAIL PROTECTED] writes: Not for me, GHC 5.04.2 (Solaris). here it goes right the first time, but then i have to type two more letters (in this case 'b\n') to get it to respond to hello. Solaris has a slightly bizarre buffering scheme in raw

Re: Floats and Doubles

2002-11-12 Thread Lennart Augustsson
Yes, they all seem to be right. You get these funny effects because numbers like 5.2 do not have an exact representation with floating point numbers in base to (like Float and Double most likely have on your machine). The number 5.2 is stored as a slightly different number as a Float, but the

Re: Behaviour of div mod with negative arguments?

2002-09-25 Thread Lennart Augustsson
Dr Mark H Phillips wrote: Hi, Does Haskell specify how div and mod should behave when given one or both arguments negative? Yes, section 6.4.2 gives an exact definition. P.S. I notice in hugs if I type -1 `div` 3 the `div` binds to the 1 and 3 first, and only applies the - at the end. Is

<    3   4   5   6   7   8   9   10   11   >