Re: pattern-matching extension?

2003-12-08 Thread Derek Elkins
On Mon, 8 Dec 2003 15:37:46 +1100
Fergus Henderson <[EMAIL PROTECTED]> wrote:

> On 05-Dec-2003, Derek Elkins <[EMAIL PROTECTED]> wrote:
> > "Abraham Egnor" <[EMAIL PROTECTED]> wrote:
> > > I've occasionally wanted some sort of equivalent of an instanceOf
> > > function in haskell, i.e. one that would let me define a function
> > > that could dispatch on the type of its argument as well as the
> > > value.  One option I've seen for this is
> > > "http://okmij.org/ftp/Haskell/class-based-dispatch.lhs";, but that
> > > unfortunately has the downside of requiring you to write both a
> > > constructor for PACK and an instance of Packable for each type
> > > you'd like to dispatch on.
> > > 
> > > The thought occurred to me that it is (intuitively) natural to do
> > > this via extending the pattern-matching facility to include types
> > > as well as literal values, i.e. something like:
> > > 
> > > f :: a -> String
> > > f (a :: Int) = "got an int, incremented: "++(show (a+1))
> > > f (a :: Show q => q) = "got a showable: "++(show a)
> > > f _ = "got something else"
> > > 
> > > This has a couple of nice features - it's a simple extension of
> > > the syntax, and acts as a sort of type-safe typecast.  However, I
> > > have zero knowledge of how hard it would be to implement this, and
> > > there may be theoretical difficulties I haven't seen.  Thoughts?
> ...
> > data Showable = forall a. Show a => Showable a
> > 
> > instance Show Showable where
> > show (Showable showable) = show showable
> > 
> > -- extension: pattern guards (I think Hugs has them but I don't
> > think-- NHC does. They are only used for prettiness here.)
> > f :: Dynamic -> String
> > f val | Just (a :: Int) <- fromDynamic val
> > = "got an int, incremented: "++show (a+1)
> >   | Just (a :: Showable) <- fromDynamic val
> > = "got a showable: "++show a
> 
> Casting to a "Showable" is not the same as a dynamic class cast.  

I agree.  In the "..." above, I say "What you could do today".

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


Re: pattern-matching extension?

2003-12-07 Thread Fergus Henderson
On 05-Dec-2003, Derek Elkins <[EMAIL PROTECTED]> wrote:
> "Abraham Egnor" <[EMAIL PROTECTED]> wrote:
> > I've occasionally wanted some sort of equivalent of an instanceOf
> > function in haskell, i.e. one that would let me define a function that
> > could dispatch on the type of its argument as well as the value.  One
> > option I've seen for this is
> > "http://okmij.org/ftp/Haskell/class-based-dispatch.lhs";, but that
> > unfortunately has the downside of requiring you to write both a
> > constructor for PACK and an instance of Packable for each type you'd
> > like to dispatch on.
> > 
> > The thought occurred to me that it is (intuitively) natural to do this
> > via extending the pattern-matching facility to include types as well
> > as literal values, i.e. something like:
> > 
> > f :: a -> String
> > f (a :: Int) = "got an int, incremented: "++(show (a+1))
> > f (a :: Show q => q) = "got a showable: "++(show a)
> > f _ = "got something else"
> > 
> > This has a couple of nice features - it's a simple extension of the
> > syntax, and acts as a sort of type-safe typecast.  However, I have
> > zero knowledge of how hard it would be to implement this, and there
> > may be theoretical difficulties I haven't seen.  Thoughts?
...
> data Showable = forall a. Show a => Showable a
> 
> instance Show Showable where
> show (Showable showable) = show showable
> 
> -- extension: pattern guards (I think Hugs has them but I don't think
> -- NHC does. They are only used for prettiness here.)
> f :: Dynamic -> String
> f val | Just (a :: Int) <- fromDynamic val
> = "got an int, incremented: "++show (a+1)
>   | Just (a :: Showable) <- fromDynamic val
> = "got a showable: "++show a

Casting to a "Showable" is not the same as a dynamic class cast.  For the
approach that you have suggested to work, the user of this function f
would need to explicitly wrap up any showable values in a "Showable"
before calling f.  This is a leaky abstraction: in general the caller
may need to know a lot about the implementation of f in order to call
it properly.  So it would be nice to have a way of doing dynamic class
cast, rather than just dynamic type cast.

However, there are some theoretical difficulties with dynamic type
class cast.  In particular, it has some nasty interactions with dynamic
loading.  If you dynamically load a new module which has some new instance
declarations, then it may affect the results of dynamic type class casts.

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
The University of Melbourne |  of excellence is a lethal habit"
WWW:   | -- the last words of T. S. Garp.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: pattern-matching extension?

2003-12-06 Thread Ralf Laemmel
As Bernie and Derek already pointed out, in principle, the rich work on
intensional polymorphism and dynamic typing comes to mind. In
particular, dynamics are readily supported in Haskell.
Let me add the following.

Type-safe cast is now clearly localised in the module Data.Typeable.
(Due to a refactoring from last summer, which will be effective in GHC 6.2)
Here I recall the type of type-safe cast as used in "scrap your 
boilerplate":

cast :: (Typeable a, Typeable b) => a -> Maybe b

No detouring to Dynamics needed.
Having *type-safe cast* means that you can also perform *type case*.
So here we go.

import Data.Typeable

We now define a function along the lines of what you asked for.
(I will discuss below the limitations of this.)
f :: (Show a, Typeable a) => a -> String
f a = (maybe (maybe others
   float (cast a) )
   int   (cast a) )
  
where
  
 -- do something with ints
 int :: Int -> String
 int a =  "got an int, incremented: " ++ show (a + 1)
  
 -- do something with floats
 float :: Float -> String
 float a = "got a float, multiplied by .42: " ++ show (a * 0.42)
  
 -- do something with all other typeables
 others = "got something else: " ++ show a

  
Full examples and relevant Data.* modules at
http://www.cs.vu.nl/boilerplate/#suite
(see "Type-case demo")

Discussion:

--

- So type case works fine. I agree with you that having syntax for
 type case  (instead of folding over maybies as I do above) would be great.
--

- Your example asks for more. It asks for what I would call
  "type-class case". You want to cast values whose
  type possibly instantiates this or that class, for example, the Show 
class.

  I agree that this would be cool to have. Especially when programming
  with generics, one sometimes wants to do what you just demonstrated:
  show things.
  It is not clear to me how many users such a language
  extension would have however. It is a major extension. Just look at
  the type of your "f". It pretends to be parametrically polymorphic.
  So an argument would not carry any class dictionaries. When doing
  the type-class case, these dictionaries had to be "invented". Nice
  research topic!!!
--

- Your particular syntax is problematic in two respects.

 1.
 The type of "f" looks too innocent. There is some preference (not a dogma)
 in Haskell that unconstrained type variables stand for parametric 
polymorphism.

 2.
 One would maybe want to use another symbol than "::" because otherwise
 one could get accidentally well-typed patterns.
--

- The specific "type-class case" for Show is of course not necessary if
 all relevant values are known to be showable. So we can go for the Data
 rather than the Typeable class. Then my example becomes as follows:
f :: Data a => a -> String
f a = -- as before
where
 -- do something with all other data
 -- NOTE the gshow as opposed to show
 others = "got something else: " ++ gshow a
Ralf

Abraham Egnor wrote:

I've occasionally wanted some sort of equivalent of an instanceOf function
in haskell, i.e. one that would let me define a function that could
dispatch on the type of its argument as well as the value.  One option
I've seen for this is
"http://okmij.org/ftp/Haskell/class-based-dispatch.lhs";, but that
unfortunately has the downside of requiring you to write both a
constructor for PACK and an instance of Packable for each type you'd like
to dispatch on.
The thought occurred to me that it is (intuitively) natural to do this via
extending the pattern-matching facility to include types as well as
literal values, i.e. something like:
f :: a -> String
f (a :: Int) = "got an int, incremented: "++(show (a+1))
f (a :: Show q => q) = "got a showable: "++(show a)
f _ = "got something else"
This has a couple of nice features - it's a simple extension of the
syntax, and acts as a sort of type-safe typecast.  However, I have zero
knowledge of how hard it would be to implement this, and there may be
theoretical difficulties I haven't seen.  Thoughts?
Abe

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



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


Re: pattern-matching extension?

2003-12-05 Thread Bernard James POPE
Abe writes:
> The thought occurred to me that it is (intuitively) natural to do this via
> extending the pattern-matching facility to include types as well as
> literal values, i.e. something like:
> 
> f :: a -> String
> f (a :: Int) = "got an int, incremented: "++(show (a+1))
> f (a :: Show q => q) = "got a showable: "++(show a)
> f _ = "got something else"
> 
> This has a couple of nice features - it's a simple extension of the
> syntax, and acts as a sort of type-safe typecast.  However, I have zero
> knowledge of how hard it would be to implement this, and there may be
> theoretical difficulties I haven't seen.  Thoughts?

Certainly seems like a useful thing to be able to do.

Systems along the same lines have been discussed in the literature,
for example:

@article{MLdynamics,
  author = {X. Leroy and M. Mauny},
  title = {Dynamics in {ML}},
  journal = {Journal of Functional Programming},
  year = 1993,
  volume = 3,
  number = 4,
  pages = {431--463}
}

@phdthesis{Dornan98,
  author=   {C. {Bentley Dornan}},
  title={Type-Secure Meta-Programming},
  school=   {Faculty of Engineering, University of Bristol},
  year= {1998},
  address=  {Bristol, United Kingdom},
}

@inproceedings{Pil98,
author = {M. Pil},
editor = {K. Hammond and A. Davie and C. Clack}, 
title = {Dynamic Types and Type Dependent Functions},
booktitle = {Implementation of Functional Languages},
pages = {169--185},
year = {1998},
volume = {LNCS 1595},
}

Cheers,
Bernie.
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: pattern-matching extension?

2003-12-05 Thread Derek Elkins
On Wed, 03 Dec 2003 15:10:07 -0500
"Abraham Egnor" <[EMAIL PROTECTED]> wrote:

> I've occasionally wanted some sort of equivalent of an instanceOf
> function in haskell, i.e. one that would let me define a function that
> could dispatch on the type of its argument as well as the value.  One
> option I've seen for this is
> "http://okmij.org/ftp/Haskell/class-based-dispatch.lhs";, but that
> unfortunately has the downside of requiring you to write both a
> constructor for PACK and an instance of Packable for each type you'd
> like to dispatch on.
> 
> The thought occurred to me that it is (intuitively) natural to do this
> via extending the pattern-matching facility to include types as well
> as literal values, i.e. something like:
> 
> f :: a -> String
> f (a :: Int) = "got an int, incremented: "++(show (a+1))
> f (a :: Show q => q) = "got a showable: "++(show a)
> f _ = "got something else"
> 
> This has a couple of nice features - it's a simple extension of the
> syntax, and acts as a sort of type-safe typecast.  However, I have
> zero knowledge of how hard it would be to implement this, and there
> may be theoretical difficulties I haven't seen.  Thoughts?

Dynamics let you do this to some extent and using pattern guards gives
you a reasonable syntax for it.  Clean has syntax like the above for
handling Dynamics and it also supports polymorphic values if I'm not
mistaken.  Dynamics in Haskell as currently implemented are only
monomorphic.  What you could do today is the following... (untested)

{-# OPTIONS -fglasgow-exts #-}
-- you should be able to get something similar in both Hugs and NHC

import Data.Dynamic

-- extension: local existentials (I think NHC only has local universals
-- you can use those to get existentials though.)
data Showable = forall a. Show a => Showable a

instance Show Showable where
show (Showable showable) = show showable

-- extension: pattern guards (I think Hugs has them but I don't think
-- NHC does. They are only used for prettiness here.)
f :: Dynamic -> String
f val | Just (a :: Int) <- fromDynamic val
= "got an int, incremented: "++show (a+1)
  | Just (a :: Showable) <- fromDynamic val
= "got a showable: "++show a
  | otherwise = "got something else"

There are other things you could do, but this seems closest to what you
are looking for.

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


pattern-matching extension?

2003-12-05 Thread Abraham Egnor
I've occasionally wanted some sort of equivalent of an instanceOf function
in haskell, i.e. one that would let me define a function that could
dispatch on the type of its argument as well as the value.  One option
I've seen for this is
"http://okmij.org/ftp/Haskell/class-based-dispatch.lhs";, but that
unfortunately has the downside of requiring you to write both a
constructor for PACK and an instance of Packable for each type you'd like
to dispatch on.

The thought occurred to me that it is (intuitively) natural to do this via
extending the pattern-matching facility to include types as well as
literal values, i.e. something like:

f :: a -> String
f (a :: Int) = "got an int, incremented: "++(show (a+1))
f (a :: Show q => q) = "got a showable: "++(show a)
f _ = "got something else"

This has a couple of nice features - it's a simple extension of the
syntax, and acts as a sort of type-safe typecast.  However, I have zero
knowledge of how hard it would be to implement this, and there may be
theoretical difficulties I haven't seen.  Thoughts?

Abe

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