Re: [Haskell] threading mutable state through callbacks

2004-10-13 Thread Keean Schupke
There are stToIO and ioToST sunctions though (ioToST is unsafe)... Keean Jules Bean wrote: On 13 Oct 2004, at 13:14, MR K P SCHUPKE wrote: its almost commutative Does that have something to do with splitting the supply? That is an approach to getting unique values, I think. newIORef why not use

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

2004-11-05 Thread Keean Schupke
I don't quite understand this thread - There are already the equivalent of IOrefs in the ST monad called STrefs. You can do newSTRef etc... you can use stToIO to embed an ST operation in the IO monad and this is safe. You can also use the unsafe ioToST, provided you are careful. To me adding

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

2004-11-05 Thread Keean Schupke
Okay, now for the purposes of my understanding, let me explore this: myRef :: IORef Int myRef = unsafePerformIO $ newIORef 0 This should always return the same reference, whereas: myIORef :: IO (IORef Int) myIORef = newIORef 0 Will return a new reference every time. I agree it would seem that the

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

2004-11-06 Thread Keean Schupke
The problem I see here is how to proove the IO in safeIO is indeed safe. Perhaps UnsafeIO is a better name, as infact the IO is still unsafe - the compiler has to take special notice of this type and not inline its definitions. Your oneShot function has the same problem - if the compiler inlines

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

2004-11-06 Thread Keean Schupke
Vincenzo Ciancia wrote: Yes, but I guess everybody would like a solution where myRef1 = unsafePerformIO $ newIORef 0 myRef2 = unsafePerformIO $ newIORef 0 are different variables. Also, it's not true that it's perfectly safe, I don't understant this - they would be different variables with

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

2004-11-06 Thread Keean Schupke
Just been reading arround. According to ghc docs, the noinline pragma is in the Haskell98 report. On that basis what is wrong with using the following to initialise these top-level constants? {-# NOINLINE newref #-} newref :: IORef Int newref = unsafePerformIO $ newIORef 0 Keean.

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

2004-11-06 Thread Keean Schupke
the related research project DIAMOND: http://www.ki.informatik.uni-frankfurt.de/research/diamond/en/ Cheers, David Keean Schupke wrote: The problem I see here is how to proove the IO in safeIO is indeed safe. Perhaps UnsafeIO is a better name, as infact the IO is still unsafe - the compiler has

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

2004-11-06 Thread Keean Schupke
David Sabel wrote: The main reason is: Nobody asks for it. Actually I think Simon Marlow has talked in the past about wanting to make GHC only do safe optimisations on unsafePerformIO. I conjecture, a problem is: if you use FUNDIO as a semantics for Haskell, you have to give up referential

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

2004-11-07 Thread Keean Schupke
Adrian Hey wrote: I'm not at all convinced, having not seen or groked either the before or after code. Perhaps you could show how this would work with an even simpler example, the one that I posted concerning the use of oneShot to create a top level (I.E. exportable) userInit. AFAICS the only

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

2004-11-08 Thread Keean Schupke
However, turning Haskell into O'Haskell seems like a far more radical suggestion than the (IMO) conservative language extension under discussion. So I don't expect it to happen anytime soon. Maybe if Haskell ever gets a better records/modules system things might look a bit different. But there

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

2004-11-08 Thread Keean Schupke
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 real world example of

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

2004-11-08 Thread Keean Schupke
Krasimir Angelov wrote: Note that 2-rank type of runSTInit doesn't allow to execute regular IO actions. Even that (ST s a) allows actions like readRef and writeRef. This allows to initialise local references but doesn't allow to access other toplevel reverences since they are bound to RealWorld

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

2004-11-08 Thread Keean Schupke
Note that 2-rank type of runSTInit doesn't allow to execute regular IO actions. Even that (ST s a) allows actions like readRef and writeRef. This allows to initialise local references but doesn't allow to access other toplevel reverences since they are bound to RealWorld state. Thinking about

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

2004-11-08 Thread Keean Schupke
Krasimir Angelov wrote: ered on top of ST and the stToIO is the lifting function. What does 'automatically be lifted' mean? Krasimir For example with the state monad you can define: instance (MonadState st m,MonadT t m) = MonadState st (t m) where update = up . update setState = up .

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

2004-11-12 Thread Keean Schupke
Hmm... It is impossible to write a purely functional program to generate random numbers. Not only that it is impossible for a computer to generate random numbers (except using hardware like a noise generator). Pseudo random numbers require a seed. Functional programs by definition only depend

Re: [Haskell] How to close a type class

2004-11-12 Thread Keean Schupke
Marcin 'Qrczak' Kowalczyk wrote: [EMAIL PROTECTED] writes: Thus we have reduced the problem of excluding certain types from a typeclass to the problem of excluding all types from one particular typeclass: Fail. How can we prevent the user from adding instances to Fail? By not exporting its

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

2004-11-12 Thread Keean Schupke
collected from real world events - so you can see this problem is not limited to haskell but to all programming languages. If you want randomness in 'C' you have to seed the generator as well. Keean. Jerzy Karczmarczuk wrote: This is my *last* word, promised... Keean Schupke wrote: Hmm

Re: [Haskell] How to close a type class

2004-11-12 Thread Keean Schupke
Just spotted this typo: How can we prevent the user from adding instances to Fail, whilst still exporting Fail so that it can be used in the constraints of other classes, like: class MustBeInt a instance MustBeInt a instance MustBeInt Int instance Fail a = MustBeInt a Keean

Re: [Haskell] Re: Parameterized Show

2004-11-15 Thread Keean Schupke
Do you need a language extension at all? You can certainly do it with the existing extensions! data ShowDict a instance Show (ShowDict a) where showsPrec _ (ShowDict a) = ... Keean George Russell wrote: Graham Klyne wrote (snipped): I like the principle of parameterizing Show to allow for

Re: [Haskell] Re: Parameterized Show

2004-11-15 Thread Keean Schupke
Easy: data ShowHex a instance Show (ShowHex a) where showsPrec _ (ShowHex a) = showHex a main = putStrLn $ (show (ShowHex 27)) Here, with labelled instances you would write: show ShowHex 27 instead you write: show (ShowHex 27) Keean. George Russell wrote: Keean Schupke

Re: [Haskell] Re: Parameterized Show

2004-11-15 Thread Keean Schupke
_ a = showDict a main = putStrLn $ (test ShowHex 27) Keean. Keean Schupke wrote: Easy: data ShowHex a instance Show (ShowHex a) where showsPrec _ (ShowHex a) = showHex a main = putStrLn $ (show (ShowHex 27)) Here, with labelled instances you would write: show ShowHex 27 instead you write

Re: [Haskell] Closed Projections on HLists?

2004-11-21 Thread Keean Schupke
Jared Warren wrote: But is there no way things could be changed so we can write (to use an example without projection to HNil): * hProject (hProject (hCons hZero hNil)) :: HCons HZero HNil ___ Haskell mailing list [EMAIL PROTECTED]

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

2004-11-22 Thread Keean Schupke
Adrian Hey wrote: Just repeating this again and again doesn't make it any more true. Ditto... I for one think the best solution is to use the language as intended and pass the values as function arguments. As pointed out on this list - the only possible situation where you cannot do this is when

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

2004-11-23 Thread Keean Schupke
Is this a joke? Seriously if you writing the OS in haskell this is trivial, you fork a thread using forkIO at system boot to maintain the driver, all 'processes' communicate to the thread using channels, the thread maintains local state (an IORef, or just a peramiter used recursively) myDriver

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

2004-11-23 Thread Keean Schupke
Adrian Hey wrote: I guess you mean the usual handle based approach, but this makes no sense at all for a Haskell interface to some *unique* stateful resource (eg. a piece of raw hardware or badly designed C library). The handle is a completely redundant argument to all interface functions (there's

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

2004-11-23 Thread Keean Schupke
Okay - but then you can keep state in haskell by using a driver thread and channels like in the example I posted. I guess I should have said it is best practice to check the real state rather than a (possibly wrong) copy. Keean. Benjamin Franksen wrote: On Tuesday 23 November 2004 10:39, Keean

Re: [Haskell] Real life examples

2004-11-24 Thread Keean Schupke
Okay, I have reconsidered, and I think I would be happy with top-level TWI's providing they can be qualified on import, for example: module Main where import Library as L1 import Library as L2 main :: IO () main = do L1.do_something_with_library

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

2004-11-24 Thread Keean Schupke
can see that we could try and open the device again, however the OS would either multiplex or serialize the device depending on type. Keean. Adrian Hey wrote: On Tuesday 23 Nov 2004 9:29 am, Keean Schupke wrote: Is this a joke? No. Seriously if you writing the OS in haskell

Re: [Haskell] Real life examples

2004-11-24 Thread Keean Schupke
Having admited to wavering on the edge of accepting top level TWIs, perhaps one of the supporters would like to comment on qualified importing... IE what happens to the unique property if I import 2 copies like so: module Main where import Library as L1 import Library as L2 Although

Re: [Haskell] A puzzle and an annoying feature

2004-11-25 Thread Keean Schupke
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 error: f :: Char - Char f c = let x = g c in h x -- But this definition does

Re: [Haskell] A puzzle and an annoying feature

2004-11-25 Thread Keean Schupke
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. Keean. Daan Leijen wrote: Lennart Augustsson wrote: [snip] So in what sense is this really ambiguous? I think it would

Re: [Haskell] Real life examples

2004-11-25 Thread Keean Schupke
wrote: On Wed, Nov 24, 2004 at 03:48:56PM +, Keean Schupke wrote: Having admited to wavering on the edge of accepting top level TWIs, perhaps one of the supporters would like to comment on qualified importing... IE what happens to the unique property if I import 2 copies like so

Re: [Haskell] A puzzle and an annoying feature

2004-11-25 Thread Keean Schupke
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 must have missed a

Re: [Haskell] A puzzle and an annoying feature

2004-11-26 Thread Keean Schupke
Ah, I see... Thats basically the same problem as overlapping instances then... (Which we have - but I try to avoid except where unavoidable...). Still, It seems it could be a good 'optional' feature. Keean. Lennart Augustsson wrote: Keean Schupke wrote: Daan Leijen wrote: You are right, I

Re: [Haskell] Real life examples

2004-11-26 Thread Keean Schupke
Adrian Hey wrote: Well it can be written in Haskell, but not using a module that was specifically designed to prevent this. Well, It can be written in Haskell as it stands at the moment... This proposal would break that... You want the library programmer to have final say. I want the library

Re: [Haskell] Implicit parallel functional programming

2005-01-19 Thread Keean Schupke
I have to say I disagree... I feel Haskell is highly suited to implicit parallel execution... The key to implicit parallelisation is that it is implicit - not explicit, so the programmer should feel like they are programming a sequential language. If we can assume little memory access

Re: [Haskell] Implicit parallel functional programming

2005-01-20 Thread Keean Schupke
Ben Lippmeier wrote: I thought the lazy functional languages are great for implicit parallelism thing died out some time ago - at least as far as running the programs on conventional hardware is concerned. Designing an algorithm that breaks apart a sequential lazy program into parallel chunks

Re: [Haskell] Implicit parallel functional programming

2005-01-20 Thread Keean Schupke
Bjorn Lisper wrote: A guess is that the first generation will support a shared memory model much like SMP:s of today (shared main memory with on-chip cache(s), or some other kind of local memory (-ies)). Here, I think implicit parallelism in functional languages can be a win in some situations.

Re: [Haskell] Implicit parallel functional programming

2005-01-20 Thread Keean Schupke
Bjorn Lisper wrote: It depends on what you compare with. Multicore CPU:s will probably have cores that are simpler than current processor cores, which means you will want to have some parallelism. Cf. a superscalar processor, which really in a sense is a parallel machine but where you add some

Re: [Haskell] Semantics of Haskell

2005-01-25 Thread Keean Schupke
When I looked through several papers about Haskell semantics, I found that recursive datatypes have been omitted. I believe fairly strong reasons have been given why this would be a bad thing, and would result in problems for type-inference. Haskell has iso-revursive types, which if defined

Re: [Haskell] class assosiated types, via GADTs.

2005-02-15 Thread Keean Schupke
Perhaps i'm being dumb, but I dont see the need for either GADTs or class-associated-types to do this... I am pretty sure it can be done using fundeps, using the techniques from the HList paper... of course I haven't coded it yet so there might be some problem I haven't considered. By the way

Re: [Haskell] class assosiated types, via GADTs.

2005-02-15 Thread Keean Schupke
John Meacham wrote: The main advantage of this translation over the one in the paper is that it is not intertwined with the dictionary generation and typeclass desugaring code, which is pretty hairy to begin with. Rather it is an orthogonal transformation so hopefully will be easier to implement

Re: [Haskell] class assosiated types, via GADTs or FDs

2005-02-17 Thread Keean Schupke
of CATs to the FD fragment available in GHC. - Martin Manuel M T Chakravarty writes: On Tue, 2005-02-15 at 10:16 +, Keean Schupke wrote: Perhaps i'm being dumb, but I dont see the need for either GADTs or class-associated-types to do this... I am pretty sure it can be done using

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-18 Thread Keean Schupke
Its a pity template haskell cannot define infix operators, but you could use TH like: $update rec field fn which would expand to: rec { field = fn (rec field) } Keean. S. Alexander Jacobson wrote: I don't know what it takes to get this sort of change into circulation, but I assume it

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-18 Thread Keean Schupke
Jacobson wrote: On Fri, 18 Feb 2005, Keean Schupke wrote: Its a pity template haskell cannot define infix operators, but you could use TH like: $update rec field fn which would expand to: rec { field = fn (rec field) } That doesn't help you so much if you want to update more than one field

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-20 Thread Keean Schupke
Yes, I have unreleased (yet) TH code for generating globally unique labels, and lifting records you can do: $(ttypelift [| data Record = Record { field1 :: Int, field2 :: String } |] ) and it lifts this to an HList style record with labels field1 field2 Labels are assigned unique type

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-20 Thread Keean Schupke
TH has supported multi-parameter classes for a while... new in 6.4 is support for fundeps. Keean. Benjamin Franksen wrote: Two clarifications: On Saturday 19 February 2005 22:33, Benjamin Franksen wrote: instance RecordField R Label_field1 T1 where getField (Rec x _) _ = x putField

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-24 Thread Keean Schupke
Benjamin Franksen wrote: On Sunday 20 February 2005 10:16, Daan Leijen wrote: Benjamin Franksen wrote: This library class defines the operations on a record: class RecordField r l t | r l - t where getField :: l - r - t putField :: l - t - r - r I have once written a short

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-24 Thread Keean Schupke
Keean Schupke wrote: Hmm... actually they can be used on the LHS... {-# OPTIONS -fglasgow-exts #-} module Main where class Test a b | a - b where test :: a - b newtype I = I (forall a . Integral a = a) newtype S = S (forall a . Show a = a) instance Test I Int where test _ = 7

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-24 Thread Keean Schupke
Benjamin Franksen wrote: I haven't read Daan's paper yet, but I think his translation is similar to the TIR (type indexed row) part of the HList library... Keean. Dear Keean, you should read more carefully what people write. Nowhere have I stated that I want higher-ranked *labels*. In fact,

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-24 Thread Keean Schupke
Having looked at the translation on page 10 of Daan's paper, I can see no advantage in this encoding, nor does it look like it supports higher ranked types in any way... (Infact it has the disadvantage of requiring a class per record, whereas the records in the HList paper require only a class

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-24 Thread Keean Schupke
Benjamin Franksen wrote: Sorry, I jumped to conclusions a bit too fast. I thought one could get rid of the newtype unwrapper if one applied it away. But this is nonsense because one still has the class constraint involving the newtype. It just doesn't work. I still wonder if your TH generated

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-02-24 Thread Keean Schupke
Benjamin Franksen wrote: Well at the moment this would give an error, but remember the list is heterogeneous, so you can just not give the list a type, and simply append the specific function... admitedly this is not as type-safe. hUpdateAtLabel field2 someFunction myRecord That is an

Re: [Haskell] Re: Type of y f = f . f

2005-03-01 Thread Keean Schupke
Actually none of these seem to work: {-# OPTIONS -fglasgow-exts #-} module Main where main :: IO () main = putStrLn OK d :: (forall c . b c - c) - b (b a) - a d f = f . f t0 = d id t1 = d head t2 = d fst Load this into GHCI and you get: Test.hs:11:7: Couldn't match the rigid variable `c'

Re: [Haskell] Type of y f = f . f

2005-03-01 Thread Keean Schupke
Here's a type that fits: d :: forall b a t c. (F t c b, F t a c) = t - a - b from the following code: -# OPTIONS -fglasgow-exts #-} module Main where main :: IO () main = putStrLn OK data ID = ID data HEAD = HEAD data FST = FST class F t a b | t a - b where f :: t - a - b instance F

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-03-02 Thread Keean Schupke
Ben Rudiak-Gould wrote: It does. An HList of Int,Bool,Char is isomorphic to the type (Int,(Bool,(Char,(, and selecting the Bool element will ultimately compile to code like this: case list of (_,(x,_)) - ... It doesn't need to search for the right element at runtime, and it doesn't

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-03-03 Thread Keean Schupke
Benjamin Franksen wrote: This is extremely cool. The type of unwrap is indeed general enough. Unfortunately, it doesn't help, because the result type of wrap Wrap (forall a. a - a) still isn't accepted in an instance declaration. Neither is the pair (unwrap, Wrap (forall a. a - a)) Or maybe I

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-03-04 Thread Keean Schupke
robert dockins wrote: Is that really how this is done? That doesn't seem like it can be right: instance X (a b) -- single parameter class where 'a' has an arrow kind is very different from: instance X a b-- multiple parameter class I would expect a type constructed with 'appT' to correspond

Re: [Haskell] Proposal: Allow \= for field update in record update syntax

2005-03-05 Thread Keean Schupke
Well it does have some validity, but I am not sure its from category theory... A type is a set of values (constructors): data Type = Constr1 | Constr2 | Constr3 likewise a class is a set of types (IE we lift one level) class Class instance Class Type1 instance Class Type2 instance Class Type3 So

Re: [Haskell] The FunctorM library

2005-03-24 Thread Keean Schupke
Why not just have the new definition with a different import path, so that legacy code continues to do: import Control.Monad And new code could do: import Control.Category.Monad (or something) And we could take this opportunity to incorporate premonads... class Functor f -- defines fmap class

Re: [Haskell] Haskell 6.4 perfomance

2005-03-24 Thread Keean Schupke
Think this should really go to glasgow-haskell-users... If this is true - how do I get ghc to use C--, and is it really faster than using gcc as a backend with all the bells whistles turned on (for a pentium-III) something like -O3 -mcpu=pentium3 -march=pentium3 -pipe -fomit-frame-pointer

Re: [Haskell] Eternal Compatibility In Theory

2005-05-03 Thread Keean Schupke
robert dockins wrote: Is there a way to reliably and automatically check if two versions of a haskell module are interface compatible? No, because it would have to check whether the semantics of functions is the same, even if they are written differently. Of course, we cannot expect

Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-08 Thread Keean Schupke
Can't you do automatic lifting with a Runnable class: class Runnable x y where run :: x - y instance Runnable (m a) (m a) where run = id instance Runnable (s - m a) (s - m a) where run = id instance (Monad m,Monad n,MonadT t m,Runnable (m a) (n a)) = Runnable

Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-09 Thread Keean Schupke
Malcolm Wallace wrote: Wolfgang Jeltsch [EMAIL PROTECTED] writes: I'm not sure exactly what you have in mind. Obviously I want something that applies to all functions, with any number of arguments, and not just (+). Furthermore, it should handle cases like 1+[2,3] where only one value is

Re: [Haskell] Mixing monadic and non-monadic functions

2005-09-09 Thread Keean Schupke
Keean Schupke wrote: I'm not sure exactly what you have in mind. Obviously I want something that applies to all functions, with any number of arguments, and not just (+). Furthermore, it should handle cases like 1+[2,3] where only one value is monadic. Just noticed the 1+[1,2] case... I am

Re: Records (was Re: [Haskell] Improvements to GHC)

2005-11-24 Thread Keean Schupke
you can always do: case (field1 record,field2 record, field3 record ...) of (pat1,pat2,pat3) - _ - Which lets you pattern match on fields independantly of their position in the record. Keean. David Roundy wrote: On Wed, Nov 23, 2005 at 02:58:43PM +0100, Wolfgang Jeltsch

Re: [Haskell] Re: ANN: HDBC (Haskell Database Connectivity)

2006-01-08 Thread Keean Schupke
My solution to this when developing a database library for my own use was to define the API in a bracket notation style, and only provide safe functions. The idea is that the function obtains the resource, calls a function passed as an argument, then frees the resource, so all resouces are

Re: [Haskell] Re: ANN: HDBC (Haskell Database Connectivity)

2006-01-13 Thread Keean Schupke
enough about the changes I was making for readability... Keean Benjamin Franksen wrote: On Monday 09 January 2006 10:03, Axel Simon wrote: On Sun, 2006-01-08 at 14:51 +, Keean Schupke wrote: My solution to this when developing a database library for my own use was to define

Re: [Haskell] Haskell DB bindings (was Re: ANN: HDBC (Haskell Database Connectivity)

2006-01-13 Thread Keean Schupke
Erm, has nobody replied to this yet? I want a robust interface, that uses bracket notation all the way down, so that any error is caught and resources are freed appropriately without the use of finalizers (which may not get run and lead to resource starvation - they are not reliable if dealing

Re: [Haskell] Re: Haskell DB bindings (was Re: ANN: HDBC (Haskell Database Connectivity)

2006-01-17 Thread Keean Schupke
John wrote: On 2006-01-14, Keean Schupke [EMAIL PROTECTED] wrote: Erm, has nobody replied to this yet? I want a robust interface, that uses bracket notation all the way down, so that any error is caught and resources are freed appropriately without the use of finalizers (which may

Re: [Haskell] Simple IO Regions

2006-01-17 Thread Keean Schupke
I really like this Oleg... I think I will use this myself as much as possible in future... As my DB code already uses bracket notation and an opaque/abstract DB handle type, it should be quite easy to incorporate this, without changing the interface... Cool! Regards, Keean. [EMAIL

Re: deriving...

2004-10-17 Thread Keean Schupke
for a template-haskell splice $(derivingX) when the compiler encounters a deriving X statement that is not built-in? Ulf Norell wrote: Keean Schupke [EMAIL PROTECTED] writes: Yes, I could quite easily write the generator in TemplateHaskell (have played with it before) _but_ I don't like

GHC CVS HEAD bug!

2004-11-03 Thread Keean Schupke
The CVS HEAD branch of GHC seems to ignore the fixity of type constructors imported from another module... This breaks compiling of code that uses this feature: module1: type a b = a :+ b infixr 1 :+ module2: a :: Int :+ Float :+ Double a = undefined Gives a the wrong type. Keean

GHC bug typo...

2004-11-03 Thread Keean Schupke
obviously I meant: type a :+ b = (a,b) In that last post! ___ Glasgow-haskell-users mailing list [EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

typechecking too eager?

2004-11-07 Thread Keean Schupke
The following code should compile (If the constructor is valid, so is the function): data Test = Test (forall a . a) test a = Test a However this fails to compile with the following error: Test.hs:9:9: Inferred type is less polymorphic than expected Quantified type variable `a' escapes

Re: typechecking too eager?

2004-11-07 Thread Keean Schupke
So, does that mean that ideally we would like it to type check, but for implementation reasons it cannot easily be done without a type signature? I can use the type signature no problem. Keean. Andres Loeh wrote: Hi there, The following code should compile (If the constructor is valid, so is

Problems with CABAL in GHC head.

2004-11-15 Thread Keean Schupke
Trying to recompile GHC (for the template-haskell existential support), but keeps failing on CABAL (the import for Foreign.Marshal.Alloc is missing from ghc/lib/compat/Distribution/Version.hs as well as import paths for Data/Version.hi which is not compiled yet as it depends on ghc-inplace.

Re: Bug in touchForeignPtr?

2004-11-22 Thread Keean Schupke
Some thoughts on this, Whilst I agree that finalizers are best avoided, it must be possible to order the finalizers for running on exit... Perhaps a simple multi-pass algorith would do? (ie: run all finalizers that do not refer to other objects with finalizers - repeat until no objects with

Re: Bug in touchForeignPtr?

2004-11-22 Thread Keean Schupke
Nope there are some unix resources that c exit routines do not free like semaphores. Sven Panne wrote: Keean Schupke wrote: [...] Whatever happens I think it must make sure all system resources allocated by a program are freed on exit - otherwise the machine will have a resource leak

Re: Bug in touchForeignPtr?

2004-11-22 Thread Keean Schupke
Semaphores (SYSV style) are not freed automatically. Currenly I am using C's at_exit funtion (which is even called on a signal)... Perhaps this is the way to deal with foreign resources... bracket notation and at_exit to clean up on signals? Keean. Sven Panne wrote: Keean Schupke wrote: Nope

Re: Bug in touchForeignPtr?

2004-11-23 Thread Keean Schupke
How can I put this, it is a best efforts approach - it does its best to run the finalizers, even after a segmentation fault... however some of the pointers may be messed up... If the cleanup causes a segmentation fault (sometimes called a double bus fault) then we have to abandon the cleanup.

instances for bottom?

2004-11-23 Thread Keean Schupke
I was wondering whether the method by which default types are chosen for unresolved overloading could be made available to the programmer. It seems that if we consider the overlapping instances: class x instance Int instance Float instance x x overlaps with Int and Float... I was

Re: Bug in touchForeignPtr?

2004-11-23 Thread Keean Schupke
Simon Marlow wrote: Note that the GC only starts the finaliser thread. The program can still terminate before this thread has run to completion (this is one reason why we say that finalisers don't always run before program termination). This sounds like a bug to me... surely you should wait

Re: -fallow-incoherent-instances

2004-11-30 Thread Keean Schupke
Ralf Laemmel wrote: General conclusion: I still have to see a good reason to use -fallow-incoherent-instances. It's mostly good to shot yourself in the head. Maybe one day we will get -fallow-backtracking? now that would be useful... Keean. ___

Re: Scoped type variables

2004-12-17 Thread Keean Schupke
what about having -fno-lexically-scoped-types for old code? Keean. Simon Peyton-Jones wrote: OK, OK, I yield! This message is about lexically scoped type variables. I've gradually become convinced that if you write f :: [a] - [a] f x = body then the type variable 'a' should be

Re: dummy variables

2004-12-29 Thread Keean Schupke
Except for GHC, where a variable staring with an '_' will not report a warning if it is unused in the body of a funtion: let _ = x in y -- no warning let result = x in y -- waring about result being unused let _result = x in y -- no warning, but variable can still be used. Keean.

Re: recursive group context bug?

2005-01-17 Thread Keean Schupke
You cannot sequence two operations from different monads... p has type: m (IO ()) id has type, IO () (in this case because this is what p returns)... You can do: p :: (Monad m) = m (IO ()) p = q = (\a - return a) Or p :: (Monad m) = m (IO ()) p = run q = id -- provided an overloaded

Re: recursive group context bug?

2005-01-17 Thread Keean Schupke
Got the wrong type sig there... p :: IO () p = run q = id Keean. ___ Glasgow-haskell-users mailing list Glasgow-haskell-users@haskell.org http://www.haskell.org/mailman/listinfo/glasgow-haskell-users

Re: recursive group context bug?

2005-01-17 Thread Keean Schupke
. Tomasz Zielonka wrote: On Mon, Jan 17, 2005 at 09:52:18AM +, Keean Schupke wrote: You cannot sequence two operations from different monads... Note that this compiles: module Bug where p :: IO (); p = q = id; q :: (Monad m) = m (IO ()); q = return (return ()); -- the only

Re: recursive group context bug?

2005-01-17 Thread Keean Schupke
This must be a bug then, because the following works! y :: Num a = a y = fromIntegral (y::Int) A simpler example might be: x :: Int x = y y :: Num a = a y = fromIntegral x I have not studied the report to see if this should be legal. ___

Re: Contents of Glasgow-haskell-users Digest, Vol 17, Issue 8

2005-01-18 Thread Keean Schupke
Jost Berthold wrote: In order to force the *complete* evaluation of your result, you could use Evaluation Strategies. Strategies are a concept introduced for increasing parallelism in Glasgow parallel Haskell. Parallelism and lazy evaluation are in a way contrary aims, since you want your parallel

Re: Contents of Glasgow-haskell-users Digest, Vol 17, Issue 8

2005-01-18 Thread Keean Schupke
Jost Berthold wrote: execution unit to do something more useful. Yes: the compiler could do a strictness analysis and hopefully (safe analysis) tell wether neededList is needed by mungeForResult. In the case of algebraic data structures (like lists), things get a bit more complex (different

Implicit parameters:

2005-01-19 Thread Keean Schupke
Question regarding implicit parameters... The GHC manual says: Dynamic binding constraints behave just like other type class constraints in that they are automatically propagated. But the following code produces an error:

Re: Implicit parameters:

2005-01-19 Thread Keean Schupke
Yes, adding -fno-monomorphism-restriction allows the example to compile. I guess I got confused by the error message, expecting it to mention the monomorphism restriction directly... I'm sure it does sometimes. Any chance of improving the error message for this? Jorge Adriano Aires wrote: Isn't it

Re: Restricted Types and Infinite Loops

2005-02-18 Thread Keean Schupke
I seem to remember that if you define the class: class DictXMLData h = XMLData h ... instance (Data d a,XMLNamespace a) = XMLData d where ... then providing you annotate the instance functions with the relavent scoped type variables (d and a) then the compiler will infer XMLNamespace correctly for

Re: Restricted Types and Infinite Loops

2005-02-18 Thread Keean Schupke
Having looked at some of my source code this relies on Data having a functional dependancy such that: class Data d a | d - a ... So it might not work for what you want. Keean. Keean Schupke wrote: I seem to remember that if you define the class: class DictXMLData h = XMLData h ... instance

Re: GHC 6.4 release candidates available

2005-03-02 Thread Keean Schupke
In the past having: {-# OPTIONS -fallow-overlapping-instances #-} in a module was enough to get ghci to allow the overlaps. so we do: ghci Test.hs now it does not work (but it did in 6.3), but: ghci -fallow-overlapping-instances Test.hs does... Even it Test.hs is the top level module. Keean.

Re: GHC 6.4 release candidates available

2005-03-02 Thread Keean Schupke
with the instance decl, but it doesn't (yet). A good feature request. Simon | -Original Message- | From: [EMAIL PROTECTED] [mailto:glasgow-haskell-users- | [EMAIL PROTECTED] On Behalf Of Keean Schupke | Sent: 02 March 2005 17:20 | To: Simon Peyton-Jones | Cc: glasgow-haskell-users

Re: GHC 6.4 release candidates available

2005-03-04 Thread Keean Schupke
There can only be one top level module in ghci (there can only be one module name before the '' prompt - that modules options should be in effect. The whole point of putting options at the top of the source file is so that the user/compiler of the code does not need to know which specific options

Re: GHC 6.4 release candidates available

2005-03-04 Thread Keean Schupke
Simon Marlow wrote: On 04 March 2005 12:58, Keean Schupke wrote: There can only be one top level module in ghci (there can only be one module name before the '' prompt - that modules options should be in effect. No, you can have multiple top-level module scopes in effect. See the GHCi

  1   2   3   4   >