Re: [Haskell-cafe] Proposal: deriving ShallowEq?

2005-07-19 Thread Stefan Holdermans

Ben,

I often find it useful to determine whether two objects are using the 
same constructor, without worrying about the constructors' arguments.


In Generic Haskell, you can define shallowEq, well ;), generically:

  shallowEq {| a :: * |} :: (shallowEq {| a |}) => a -> a -> Bool

  shallowEq {| Unit |} Unit Unit   = True
  shallowEq {| Sum a b |} (Inl _) (Inl _)  = True
  shallowEq {| Sum a b |} (Inr _) (Inr _)  = True
  shallowEq {| Sum a b |} _ _  = False
  shallowEq {| Prod a b |} (_ :*: _) (_ :*: _) = True
  shallowEq {| Int |} n1 n2= n1 == n2
  shallowEq {| Char |} c1 c2   = c1 == c2

There are some more lightweight variations of this style of programming 
that can be embedded in Haskell, but they require some additional 
effort per data type.


I'm not sure how this can be done with the Scrap Your Boilerplate 
approach, i.e., I have not give it too much thought yet, but I'm sure 
something can be done there too.


Regards,

Stefan

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Proposal: deriving ShallowEq?

2005-07-19 Thread Bernard Pope
On Tue, 2005-07-19 at 17:01 +1000, Ben Lippmeier wrote:
> Hello,
> 
> I often find it useful to determine whether two objects are using the 
> same constructor, without worrying about the constructors' arguments.

[snip]

> Having some sort of generic shallowEq operator reduces the need for a 
> host of predicates such as: (this one from Data.Maybe)
> 
>  > isJust x
>  >  = case x of
>  >Just {} -> True
>  >_   -> False
> 
> .. which is an approach that is obviously going to be tedious when the 
> size of the data type becomes large.
> 
> --
> There is way to hack together a partial implementation of the ShallowEq 
> class within GHC, but it leaves much to be desired:
> 
>  > instance Show a => ShallowEq a where
>  >  ([EMAIL PROTECTED]) a b
>  >= (head $ words $ show a) == (head $ words $ show b)

Ouch!

> Questions:
>   1) Does anyone know a better/existing way to implement ShallowEq that 
> doesn't involve enumerating all the constructors in the data type?
> 
>   2) If not, can anyone think of reasons why it wouldn't be a good idea 
> for GHC to derive ShallowEq (by expanding said enumeration)?

DriFT comes to mind:

   http://repetae.net/john/computer/haskell/DrIFT/

it already supplies some query operators that might make shallowEq
redundant. 

Cheers,
Bernie.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Proposal: deriving ShallowEq?

2005-07-19 Thread Henning Thielemann

On Tue, 19 Jul 2005, Ben Lippmeier wrote:

> An example, using some arbitrary data type "Thingo":
>
>  > class ShallowEq a where
>  >  shallowEq  :: a -> a -> Bool
>
>  > data Thingo a b
>  >= TOne   a
>  >| TTwo   a b Int Char Float
>  >| TThree Int Char b b
>
> Questions:
>   1) Does anyone know a better/existing way to implement ShallowEq that
> doesn't involve enumerating all the constructors in the data type?

A more general approach are projection functions like

getTOne :: Thingo a b -> Maybe a
getTOne (TOne x) = Just x
getTOne _= Nothing

Then you can map the values to be compared into a Maybe and you need only
a shallowEq for Maybe.

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Proposal: deriving ShallowEq?

2005-07-19 Thread Bulat Ziganshin
Hello Ben,

Tuesday, July 19, 2005, 11:01:32 AM, you wrote:
BL> I often find it useful to determine whether two objects are using the
BL> same constructor, without worrying about the constructors' arguments.

BL> There is way to hack together a partial implementation of the ShallowEq
BL> class within GHC, but it leaves much to be desired:

BL>  > instance Show a => ShallowEq a where
BL>  >  ([EMAIL PROTECTED]) a b
BL>  >  = (head $ words $ show a) == (head $ words $ show b)

reading GHC sources is always very interesting :)

that is from GHC/Base.hs :

%*
%*  *
[EMAIL PROTECTED]@}
%*  *
%*

Returns the 'tag' of a constructor application; this function is used
by the deriving code for Eq, Ord and Enum.

The primitive dataToTag# requires an evaluated constructor application
as its argument, so we provide getTag as a wrapper that performs the
evaluation before calling dataToTag#.  We could have dataToTag#
evaluate its argument, but we prefer to do it this way because (a)
dataToTag# can be an inline primop if it doesn't need to do any
evaluation, and (b) we want to expose the evaluation to the
simplifier, because it might be possible to eliminate the evaluation
in the case when the argument is already known to be evaluated.

\begin{code}
{-# INLINE getTag #-}
getTag :: a -> Int#
getTag x = x `seq` dataToTag# x
\end{code}




-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]



___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Proposal: deriving ShallowEq?

2005-07-19 Thread Ben Lippmeier

Bulat Ziganshin wrote:


reading GHC sources is always very interesting :)
that is from GHC/Base.hs :



getTag :: a -> Int#
getTag x = x `seq` dataToTag# x


! This is just what I was looking for, thankyou.

My shallowEq function is now simply:

shallowEq :: a -> a -> Bool
shallowEq a b = getTag a ==# getTag b

My project is already totally reliant on GHC, and this will save me the 
heartache of hacking DrIFT (which I was in the process of setting up 
when I saw this mail) into my makefile.


Portability be damned!

Ben.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Proposal: deriving ShallowEq?

2005-07-19 Thread Remi Turk
On Tue, Jul 19, 2005 at 08:16:35PM +1000, Ben Lippmeier wrote:
> Bulat Ziganshin wrote:
> 
> >reading GHC sources is always very interesting :)
> >that is from GHC/Base.hs :
> 
> >getTag :: a -> Int#
> >getTag x = x `seq` dataToTag# x
> 
> ! This is just what I was looking for, thankyou.
> 
> My shallowEq function is now simply:
> 
> shallowEq :: a -> a -> Bool
> shallowEq a b = getTag a ==# getTag b
> 
> My project is already totally reliant on GHC, and this will save me the 
> heartache of hacking DrIFT (which I was in the process of setting up 
> when I saw this mail) into my makefile.
> 
> Portability be damned!
> 
> Ben.

You might increase portability a bit by using

import Data.Generics

shallowEq :: Data a => a -> a -> Bool
shallowEq x y = toConstr x == toConstr y

it does introduce a dependency on Data though

Groeten,
Remi

-- 
Nobody can be exactly like me. Even I have trouble doing it.


pgpyTyB9kylSx.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Proposal: deriving ShallowEq?

2005-07-19 Thread Ralf Lammel
As Bulat points out, the GHC primitive dataToTag#
indeed nicely solves the problem. Ben, just for
completeness' sake; with SYB, you get such reflective
information too (and others):

shallowEq :: Data a => a -> a -> Bool
shallowEq x y = toConstr x == toConstr y

(dataToTag# returns Int, while toConstr comprises other things like the
constructor name.)

Regards,
Ralf

> -Original Message-
> From: [EMAIL PROTECTED] [mailto:haskell-cafe-
> [EMAIL PROTECTED] On Behalf Of Bulat Ziganshin
> Sent: Tuesday, July 19, 2005 1:18 AM
> To: Ben Lippmeier
> Cc: haskell-cafe@haskell.org
> Subject: Re: [Haskell-cafe] Proposal: deriving ShallowEq?
> 
> Hello Ben,
> 
> Tuesday, July 19, 2005, 11:01:32 AM, you wrote:
> BL> I often find it useful to determine whether two objects are using
the
> BL> same constructor, without worrying about the constructors'
arguments.
> 
> BL> There is way to hack together a partial implementation of the
> ShallowEq
> BL> class within GHC, but it leaves much to be desired:
> 
> BL>  > instance Show a => ShallowEq a where
> BL>  >  ([EMAIL PROTECTED]) a b
> BL>  >  = (head $ words $ show a) == (head $ words $ show b)
> 
> reading GHC sources is always very interesting :)
> 
> that is from GHC/Base.hs :
> 
> %*
> %*  *
> [EMAIL PROTECTED]@}
> %*  *
> %*
> 
> Returns the 'tag' of a constructor application; this function is used
> by the deriving code for Eq, Ord and Enum.
> 
> The primitive dataToTag# requires an evaluated constructor application
> as its argument, so we provide getTag as a wrapper that performs the
> evaluation before calling dataToTag#.  We could have dataToTag#
> evaluate its argument, but we prefer to do it this way because (a)
> dataToTag# can be an inline primop if it doesn't need to do any
> evaluation, and (b) we want to expose the evaluation to the
> simplifier, because it might be possible to eliminate the evaluation
> in the case when the argument is already known to be evaluated.
> 
> \begin{code}
> {-# INLINE getTag #-}
> getTag :: a -> Int#
> getTag x = x `seq` dataToTag# x
> \end{code}
> 
> 
> 
> 
> --
> Best regards,
>  Bulatmailto:[EMAIL PROTECTED]
> 
> 
> 
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Proposal: deriving ShallowEq?

2005-07-19 Thread Ben Lippmeier

Ralf Lammel wrote:

As Bulat points out, the GHC primitive dataToTag#
indeed nicely solves the problem. Ben, just for
completeness' sake; with SYB, you get such reflective
information too (and others):

shallowEq :: Data a => a -> a -> Bool
shallowEq x y = toConstr x == toConstr y

(dataToTag# returns Int, while toConstr comprises other things like the
constructor name.)



Ralf,
Yes, I ended up using the "propper" SYB approach instead, though I have 
noticed that the reflection data types Constr and DataRep make no 
mention of type variables or functions.


For example, this works fine:
> getTag (Just 5)   ==# getTag (Just{})
> getTag (Just (\x -> x))   ==# getTag (Just{})

But this does not
> toConstr (Just 5) == toConstr (Just{})
Ambiguous type variables.

> toConstr (Just (\x -> x)) == toConstr (Just{})
No instance for Data (t -> t)

I appreciate the reasons why this is so, though I think it's interesting 
to see the practical consequences.


A toConstr version of shallowEq works ok so long as you provide a type 
signature to constrain both arguments to be the same type, and one of 
them is always fully constructed - which is fine for me at the moment.


Ben.


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


RE: [Haskell-cafe] Proposal: deriving ShallowEq?

2005-07-19 Thread Ralf Lammel
Ben,

thanks for your clever questions.
Let's look at a little GHC 6.4 demo.

{-# OPTIONS -fglasgow-exts #-}

import Data.Generics

main = do 
  print $ toConstr ()   == toConstr ()
  print $ toConstr (5::Int) == toConstr ()
  print $ toConstr (\(x::Int) -> x) == toConstr ()
  print $ id   `shallowEq` (id::Int -> Int)

shallowEq :: Data a => a -> a -> Bool
shallowEq x y = toConstr x == toConstr y

This gives:

*Main> main
True
False
*** Exception: toConstr

Some observations:

a) We need to say what sort of Num this 5 is because otherwise instance
selection will not know how to obtain the constructor for 5. In this
sense, SYB is not different from normal type-class-based programming.
Well, modulo default declarations;
http://www.haskell.org/tutorial/numbers.html

So this works (because of a default declaration)

*Main> show 5 == show ()
False

This one doesn't because there is no default declaration:

*Main> toConstr 5 == toConstr ()

:1:0:
Ambiguous type variable `a' in the constraints: ...


b) You are right.
An independently polymorhic shallowEq is more expressive
since it allows us to compare the top-level constructors of different
specializations of the same type, e.g., Just Char vs. Just String.

shallowEq' :: (Data a, Data b) => a -> b -> Bool
shallowEq' x y = toConstr x == toConstr y

You also spotted the issue that shallowEq' cannot operate
on data of types a and b where either of these is a type scheme.

The reason for that is that the instances of Data (and Typeable)
involve constraints for the types of the children. As long as
these children types are not fixed, toConstr cannot be computed
since instance selection cannot be completed. In general, this
is a good idea because of the types of gfoldl (and the gmap
derivates), but for exercises like shallow equality this is in the way. 

I don't have a good solution to offer.
(I don't see either that this is a show stopper in practice.)
We may think of splitting up the API as to define several 
more precise classes ...

c) Just for the record, SYB's toConstr throws for function types.

Ralf

> -Original Message-
> From: [EMAIL PROTECTED] [mailto:haskell-cafe-
> [EMAIL PROTECTED] On Behalf Of Ben Lippmeier
> Sent: Tuesday, July 19, 2005 8:56 PM
> Cc: haskell-cafe@haskell.org
> Subject: Re: [Haskell-cafe] Proposal: deriving ShallowEq?
> 
> Ralf Lammel wrote:
> > As Bulat points out, the GHC primitive dataToTag#
> > indeed nicely solves the problem. Ben, just for
> > completeness' sake; with SYB, you get such reflective
> > information too (and others):
> >
> > shallowEq :: Data a => a -> a -> Bool
> > shallowEq x y = toConstr x == toConstr y
> >
> > (dataToTag# returns Int, while toConstr comprises other things like
the
> > constructor name.)
> >
> 
> Ralf,
> Yes, I ended up using the "propper" SYB approach instead, though I
have
> noticed that the reflection data types Constr and DataRep make no
> mention of type variables or functions.
> 
> For example, this works fine:
>  > getTag (Just 5)   ==# getTag (Just{})
>  > getTag (Just (\x -> x))   ==# getTag (Just{})
> 
> But this does not
>  > toConstr (Just 5) == toConstr (Just{})
>  Ambiguous type variables.
> 
>  > toConstr (Just (\x -> x)) == toConstr (Just{})
>  No instance for Data (t -> t)
> 
> I appreciate the reasons why this is so, though I think it's
interesting
> to see the practical consequences.
> 
> A toConstr version of shallowEq works ok so long as you provide a type
> signature to constrain both arguments to be the same type, and one of
> them is always fully constructed - which is fine for me at the moment.
> 
> Ben.
> 
> 
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe