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,
 Bulat                            mailto:[EMAIL PROTECTED]



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

Reply via email to