[Haskell-cafe] 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 here, it would be nice if GHC, Hugs, and NHC98 agreed on 
> something.
> Can we agree on the special Rational values below?

I would be very careful of adding non-rationals to the Rational type.
For one thing, it breaks the traditional rule for equality
  a % b == c % d iffa*d == b*c
You'd need to look at all the instances for Ratio a that are defined.
For instance, the Ord instance would require at least lots of special
cases.  And when would you expect 'x/0' to give +Infinity and when
-Infinity?  For IEEE floats, there are distinct representations of +0
and -0, which lets you know when you want which one.  But for the
Rational type there is no such distinction.

The behaviour that '1 % 0' gives the error 'Ratio.% : zero
denominator' is clearly specified by the Library Report.

In the meantime, there are utility functions for dealing with IEEE
floats (isNaN, etc.)

Peace,
Dylan


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-11-05 Thread MR K P SCHUPKE
>I would be very careful of adding non-rationals to the Rational type.

Why is there no Irrational class. This would make more sense for
Floats and Doubles than the fraction based Rational class. We could
also add an implementation of infinite precision irrationals using
a
pair of Integers for exponent and mantissa.

Keean.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-11-05 Thread Robert Dockins
My guess is because irrationals can't be represented on a discrete 
computer (unless you consider a computaion, the limit of which is the 
irrational number in question).  A single irrational might not just be 
arbitrarily long, but it may have an _infinite_ length representation! 
What you have described is arbitrary (not infinite) precision floating 
point.

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).  Perhaps it 
would make more sense to add constructors to the Rational type to 
represent these additional "values", ie, make Rational look like
(edited from section 12.1 of the Report)

data (Integral a) => Ratio a = a! :% a! |
 Nan | PosInf | NegInf
deriving(Eq)
type Rational = Ratio Integer
This has the effect that pattern matching :% when the value is NaN etc. 
gives an error instead of doing bizarre things (by succeeding against 
non numeric values).  This is an advantage or a disadvantage depending 
on your viewpoint.

Unfortunately, that isn't how its defined in the Report, so it may not 
be an option.

MR K P SCHUPKE wrote:
I would be very careful of adding non-rationals to the Rational type.

Why is there no Irrational class. This would make more sense for
Floats and Doubles than the fraction based Rational class. We could
also add an implementation of infinite precision irrationals using
a
pair of Integers for exponent and mantissa.
Keean.
___
Glasgow-haskell-users mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/glasgow-haskell-users
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-11-05 Thread Henning Thielemann

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 IEEE floating processing, as well as
0. To support this behaviour uniformly one would need a +0 or -0 offset
for each number, which would lead straightforward to non-standard analysis
... 

Prelude> 1/0.0
Infinity
Prelude> -1/0.0
-Infinity
Prelude> -0.0
-0.0
Prelude> 1.0-1.0
0.0
Prelude> -(1.0-1.0)
-0.0

Thus (a-b) is not the same as -(b-a) for IEEE floats! 

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-11-05 Thread Ben Rudiak-Gould
MR K P SCHUPKE wrote:
>Why is there no Irrational class. This would make more sense for
>Floats and Doubles than the fraction based Rational class. We could
>also add an implementation of infinite precision irrationals using
>a pair of Integers for exponent and mantissa.
That would just be a subset of the rationals, namely the dyadic 
rationals (mantissa / 2^^exponent).

-- Ben
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Making MVar and Chan Instances of Typeable

2004-11-05 Thread Benjamin Franksen
Hello Experts,

I need MVar and Chan to be instances of Typeable. Any hint on how this is most 
easily done would be greatly appreciated. I could change the libraries and 
add 'deriving Typeable' but I hesitate to do so.

Cheers,
Ben
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-11-05 Thread Ben Rudiak-Gould
Henning Thielemann wrote:
>I wonder why Infinity has a sign in IEEE floating processing, as well as
>0. To support this behaviour uniformly one would need a +0 or -0 offset
>for each number, which would lead straightforward to non-standard analysis
>...
See "Branch Cuts for Complex Elementary Functions, or Much Ado About 
Nothing's Sign Bit" by William Kahan, in The State of the Art in 
Numerical Analysis, (eds. Iserles and Powell), Clarendon Press, Oxford, 
1987.

(Note that I have not read this paper. However, Kahan was the primary 
architect of the IEEE floating point standard, so you can be pretty sure 
the reasons given in the paper are also the reasons IEEE floating point 
has signed zero.)

A good online presentation which mentions all kinds of interesting 
floating point pathologies, including those discussed in the above 
paper, is "How Java’s Floating-Point Hurts Everyone Everywhere" 
(http://www.cs.berkeley.edu/~wkahan/JAVAhurt.pdf).

>[...] Thus (a-b) is not the same as -(b-a) for IEEE floats!
Nor is x*0 equal to 0 for every x; nor does x == y imply f(x) == f(y) 
for every x, y, f; nor is addition or multiplication associative. There 
aren't many identities that do hold of floating point numbers.

-- Ben
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-11-05 Thread Benjamin Franksen
On Friday 05 November 2004 14:57, Henning Thielemann wrote:
> On Fri, 5 Nov 2004, Robert Dockins wrote:
> I wonder why Infinity has a sign in IEEE floating processing, as well as
> 0. 

As regards Inf, this makes sense, because with +Inf and -Inf order is 
preserved. With one unsigned Inf nothing is really < or > than anything else.

> To support this behaviour uniformly one would need a +0 or -0 offset 
> for each number, which would lead straightforward to non-standard analysis
> ...

It's worse: Since according to IEEE +0 is not equal to -0, atan2 is not a 
function!

Ben
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Making MVar and Chan Instances of Typeable

2004-11-05 Thread Tomasz Zielonka
On Fri, Nov 05, 2004 at 01:57:53PM +0100, Benjamin Franksen wrote:
> Hello Experts,
> 
> I need MVar and Chan to be instances of Typeable. Any hint on how this is most 
> easily done would be greatly appreciated. I could change the libraries and 
> add 'deriving Typeable' but I hesitate to do so.

The easiest way is to hide type constructor Chan:

  import Control.Concurrent
  import Data.Generics

  newtype MyChan a = MyChan (Chan a) deriving Typeable

Of course, you can also write the instance for Chan by hand.

Best regards,
Tom

-- 
.signature: Too many levels of symbolic links
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-11-05 Thread MR K P SCHUPKE
>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...

Keean.
..
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-11-05 Thread Duncan Coutts
On Fri, 2004-11-05 at 13:57, 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 IEEE floating processing, as well as
> 0. To support this behaviour uniformly one would need a +0 or -0 offset
> for each number, which would lead straightforward to non-standard analysis

It is related to the decision to have signed infinity. One rationale is
thus:

The identity
1/(1/x) = x
is only true for all IEEE floats x if we have signed 0. In particular if
x is -infinity then 1/(-infinity) would be 0 and 1/0 = +infinity in the
IEEE floating point system. So if we preserve the sign for overflow
(+-infinity), we also need to preserve the sign for underflow (+-0) or
other identities fail.

Note that -0 == +0

See: What Every Computer Scientist Should Know About Floating Point
Arithmetic
http://citeseer.ist.psu.edu/goldberg91what.html
page 183.

Duncan

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-11-05 Thread Benjamin Franksen
On Friday 05 November 2004 14:11, you wrote:
> It's worse: Since according to IEEE +0 is not equal to -0, atan2 is not a
> function!

Sorry, I meant to write: Since according to IEEE +0 *is* to be regarded as 
equal to -0, atan2 is not a function. (Because it gives different values for 
argument combinations
-0, +0.)

Ben
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Making MVar and Chan Instances of Typeable

2004-11-05 Thread Benjamin Franksen
On Friday 05 November 2004 15:51, you wrote:
> On Fri, Nov 05, 2004 at 01:57:53PM +0100, Benjamin Franksen wrote:
> > Hello Experts,
> >
> > I need MVar and Chan to be instances of Typeable. Any hint on how this is
> > most easily done would be greatly appreciated. I could change the
> > libraries and add 'deriving Typeable' but I hesitate to do so.
>
> The easiest way is to hide type constructor Chan:
>
>   import Control.Concurrent
>   import Data.Generics
>
>   newtype MyChan a = MyChan (Chan a) deriving Typeable
>
> Of course, you can also write the instance for Chan by hand.

This might be the easiest way, but is otherwise inconvenient. I tried to write 
the instances by hand. My first attempt was:

instance Typeable a => Typeable (MVar a) where
  typeOf x =
mkAppTy (mkTyCon "Control.Concurrent.MVar.MVar") [typeOf (undefined::a)]

but unfortunately this doesn't work. Ghc complains about 

Ambiguous type variable `a1' in the top-level constraint:
  `Typeable a1' arising from use of `typeOf' at Helpers.hs:8

The reason is apparently that inside the definition of typeOf the type 
variable 'a' is not unified with the 'a' from the instance header. I could 
write 

  typeOf (MVar x) =
mkAppTy (mkTyCon "Control.Concurrent.MVar.MVar") [typeOf y]
where
  y = undefined `asTypeOf` x

but the doc says that typeOf should be written without evaluating its 
argument, so that is ca be passed 'undefined'.

What I need is a trick that enables me to get at the type of the 'a' in the 
instance header for use inside definition of 'typeOf'.

Ben
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Making MVar and Chan Instances of Typeable

2004-11-05 Thread MR K P SCHUPKE
nstance Typeable a => Typeable (MVar a) where
  typeOf (x::x) =
mkAppTy (mkTyCon "Control.Concurrent.MVar.MVar") [typeOf (undefined::x)]

Keean.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-11-05 Thread Robert Dockins

 >[...] Thus (a-b) is not the same as -(b-a) for IEEE floats!
Nor is x*0 equal to 0 for every x; nor does x == y imply f(x) == f(y) 
for every x, y, f; nor is addition or multiplication associative. There 
aren't many identities that do hold of floating point numbers.
Yes, but they DO hold for Rational (I believe).  The argument against 
NaN = 0 :% 0, Inf = 1 :% 0, etc. is that the otherwise valid identies 
for _Rational_ are disturbed.

___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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

2004-11-05 Thread Marcin 'Qrczak' Kowalczyk
Benjamin Franksen <[EMAIL PROTECTED]> writes:

>> It's worse: Since according to IEEE +0 is not equal to -0, atan2 is not a
>> function!
>
> Sorry, I meant to write: Since according to IEEE +0 *is* to be regarded as 
> equal to -0, atan2 is not a function. (Because it gives different values for 
> argument combinations -0, +0.)

>From my point of view it is a function. Only == is not the finest
equality possible (but the one which is more useful).

-- 
   __("< Marcin Kowalczyk
   \__/   [EMAIL PROTECTED]
^^ http://qrnik.knm.org.pl/~qrczak/
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Making MVar and Chan Instances of Typeable

2004-11-05 Thread Benjamin Franksen
On Friday 05 November 2004 16:20, MR K P SCHUPKE wrote:
> nstance Typeable a => Typeable (MVar a) where
>   typeOf (x::x) =
> mkAppTy (mkTyCon "Control.Concurrent.MVar.MVar") [typeOf
> (undefined::x)]

I may be missing something but this look like an open recursion to me. The 
type 'x' is 'MVar a', but what is needed is the 'a'.

Ben
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Making MVar and Chan Instances of Typeable

2004-11-05 Thread Benjamin Franksen
On Friday 05 November 2004 13:57, Benjamin Franksen wrote:
> Hello Experts,
>
> I need MVar and Chan to be instances of Typeable. Any hint on how this is
> most easily done would be greatly appreciated. I could change the libraries
> and add 'deriving Typeable' but I hesitate to do so.

Ok, I found a solution but it is horrible!

module Helpers where

import Control.Concurrent
import Data.Typeable
import Foreign

instance Typeable a => Typeable (MVar a) where
  typeOf x =
mkAppTy (mkTyCon "Control.Concurrent.MVar.MVar") [typeOf y]
where
  y = unsafePerformIO $ do
z <- newEmptyMVar >>= readMVar
return (z `asTypeOf` x)

I dearly hope this can be done in a less convoluted fashion.

Ben
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Making MVar and Chan Instances of Typeable

2004-11-05 Thread Koji Nakahara
On Fri, 5 Nov 2004 14:43:55 +0100
Benjamin Franksen <[EMAIL PROTECTED]> wrote:

> the instances by hand. My first attempt was:
> 
> instance Typeable a => Typeable (MVar a) where
>   typeOf x =
> mkAppTy (mkTyCon "Control.Concurrent.MVar.MVar") [typeOf (undefined::a)]
> 
> but unfortunately this doesn't work. Ghc complains about 
> 
> Ambiguous type variable `a1' in the top-level constraint:
>   `Typeable a1' arising from use of `typeOf' at Helpers.hs:8
> 
> The reason is apparently that inside the definition of typeOf the type 
> variable 'a' is not unified with the 'a' from the instance header. I could 
> write 


You can write:

instance Typeable a => Typeable (MVar a) where
typeOf (x :: MVar a) =
mkAppTy (mkTyCon "Control.Concurrent.MVar.MVar") [typeOf (undefined::a)]


Hope it helps,
Koji Nakahara
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Making MVar and Chan Instances of Typeable

2004-11-05 Thread MR K P SCHUPKE
My mistake:

instance Typeable a => Typeable (MVar a) where
  typeOf (x::MVar x) =
mkAppTy (mkTyCon "Control.Concurrent.MVar.MVar") [typeOf (undefined::x)]

Keean.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Making MVar and Chan Instances of Typeable

2004-11-05 Thread Benjamin Franksen
On Friday 05 November 2004 15:07, Benjamin Franksen wrote:
> instance Typeable a => Typeable (MVar a) where
>   typeOf x =
> mkAppTy (mkTyCon "Control.Concurrent.MVar.MVar") [typeOf y]
> where
>   y = unsafePerformIO $ do
> z <- newEmptyMVar >>= readMVar
> return (z `asTypeOf` x)

which is wrong because it also passes the typeOf of the MVar and not the 
content. This one is correct, I hope:

instance Typeable a => Typeable (MVar a) where
  typeOf x =
mkAppTy (mkTyCon "Control.Concurrent.MVar.MVar") [typeOf v]
where
  v = unsafePerformIO $ do
y <- newEmptyMVar
readMVar (y `asTypeOf` x)

On Friday 05 November 2004 16:44, Koji Nakahara wrote:
> instance Typeable a => Typeable (MVar a) where
> typeOf (x :: MVar a) =
>   mkAppTy (mkTyCon "Control.Concurrent.MVar.MVar") [typeOf (undefined::a)]

Yes, that's it. The above is a lot more convoluted but has a small advantage: 
it doesn't need -fglasgow-exts.

I understand now, why pattern signatures were deemed a useful feature!

Thanks to all who helped.

Cheers,
Ben
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Literate Haskell and piecewise construction of classes/instances

2004-11-05 Thread Graham Klyne
I'm experimenting with a Literate Haskell style to construct a tutorial 
about Description Logics [1][2].

I'm developing the material in small sections, and using examples in the 
document to test the code as I go along .  I therefore find that I want to 
introduce the components of class and instance declarations in pieces, 
rather than having the entire declaration in a single place.  Am I right in 
thinking this is not possible?

For example, I find myself resorting to tricks like this:
[[
So far, a single Description Logic (AL) has been considered.  My next step
is to generalize the function interface to a collection of type classes
that can handle arbitrary description logics.  The basic ideas of concepts,
roles and interpretations are common to all description logics, so these
are used as defined above.  It is the concept descriptions, role descriptions
and associated operations that need to be further abstracted:
- class ConceptExpr c where
- iConcept :: Ord a => TInterpretation a -> c -> Set a
(The full and final definition of ConceptExpr is given later.)
 :
]]
and later...
[[
The class interface for concept expressions is therefore extended thus:
> class ConceptExpr c where
> iConcept  :: Ord a => TInterpretation a -> c -> Set a
> isSatisfiableWith :: TBox c -> c -> Bool
> isSatisfiableWith t c = not (isSubsumedByWith t c emptyClass)
> isSubsumedByWith  :: TBox c -> c -> c -> Bool
> isSubsumedByWith t c d =
> not $ isSatisfiableWith t (intersectClass c (complementClass d))
> emptyClass:: c
> complementClass   :: c -> c
> intersectClass:: c -> c -> c
]]
What this suggests to me is that for Literate Haskell it is desirable to 
have multiple appearances of a class/instance declaration, constrained so 
that one version contains all of the definitions contained in any other 
appearance, and no two appearances contain differing definitions for any 
component (using a fairly strict syntactic comparison to determine 
difference here).

Does this strike any chords with anyone?
#g
--
[1] http://dl.kr.org/  (Description Logics web page)
[2] http://www.ninebynine.org/Software/HaskellDL/DLExploration.lhs (My 
tutorial, work-in-progress - implements "structural subsumption" for a 
simple Description Logic.)


Graham Klyne
For email:
http://www.ninebynine.org/#Contact
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 a number of choices to be made in making such an
implementation.  It would be handy, but it makes sense that it's more
than the Haskell designers wanted to specify initially.

It would make a nice library if you want to write it.

Peace,
Dylan


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Defining Haskell using "arrows"

2004-11-05 Thread Andy Elvey
Hi all - 
   I'm a first-timer here, and am *very* much attracted by Haskell's elegance 
and power ... :-)  
  I have only poked around briefly with Haskell so far (at the "hello world" 
level).  One thing that I have come across, and which really got me thinking, 
was the page on the Haskell website about "arrows".  They really seem to take 
elegance and the "generic-ness" of algorithms to a new level.  
  I was thinking - arrows are a relatively recent concept.  Haskell's grammar 
(as defined in the Haskell report) has now been around for quite some time. 
So - I thought "what if?"  What if Haskell were to be defined (er, 
*re*-defined) in terms of arrows?  In other words, what if it were possible 
to start totally "from scratch", re-defining Haskell's grammar using arrows? 
(and preferably, *only* arrows ... ). 
  This would presumably involve somehow coding up the arrows first, and then 
(haivng got them), using them to create/define the rest of the language. 
  My reason for suggesting this - simply to see if it were possible to do a 
very small (but still quite comprehensive) Haskell implementation. Small 
meaning maybe 2-3 MB or so ...  As an interesting "benchmark" of this, the 
Rebol language (though proprietary - sigh!) - comes in at 0.5 Mb or so, 
including a GUI.  So, "very small but very powerful" is possible (although 
undoubtedly pretty difficult ... ) 
  As a Haskell newbie, I have to defer to everyone else on this list (in terms 
of my Haskell ability), but just thought I'd post this idea anyway.  I was 
thinking " I wonder if anyone has thought of this? ... " .  
  Arrows seem to be a recent "add-on", as it were, so I thought  -given their 
power and flexibility, why not turn things totally around, and put them at 
the *very core* of the language, using them to define the language itself.  
  Anyway, I'm keen to hear people's thoughts on this!  Very many thanks in 
advance ...  :-) 
  - Andy 
 
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Making MVar and Chan Instances of Typeable

2004-11-05 Thread Remi Turk
On Fri, Nov 05, 2004 at 01:57:53PM +0100, Benjamin Franksen wrote:
> Hello Experts,
> 
> I need MVar and Chan to be instances of Typeable. Any hint on how this is most 
> easily done would be greatly appreciated. I could change the libraries and 
> add 'deriving Typeable' but I hesitate to do so.
> 
> Cheers,
> Ben

It can be done in Haskell 98 the same way `asTypeOf' is defined
in the Report:

instance Typeable a => Typeable (MVar a) where
typeOf v= mkAppTy (mkTyCon "Control.Concurrent.MVar.MVar")
[typeOf (t v)]
where
t   :: a b -> b
t   = undefined

Groetjes,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] (Re arrows and Haskell) ...

2004-11-05 Thread Andy Elvey
Hi again - 
   Apologies for another post from me so soon  (and for replying to my own 
post).  
Regarding my post about arrows and Haskell (and the idea of trying to 
define Haskell's grammar in terms of arrows) - upon thinking about that, I'm 
pretty much of the opinion that it'd be an immense task ... 
   I also think that although maybe some of the grammar might be possible to 
define using arrows, it wouldn't be possible to do all of it :-) .  So, I'll 
politely "withdraw to a corner" for a little while, resolving to think a bit 
more before I post!   ;-)  
 - Andy 
 
___
Haskell-Cafe mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell-cafe