RULES pragma with class constraint

Bulat Ziganshin bulat.ziganshin at gmail.com
Mon Mar 20 07:35:30 EST 2006


Hello John,

Monday, March 20, 2006, 2:49:14 PM, you wrote:

JM> Is it possible to create a RULES that fires only if a type has a given
JM> class constraint? something like:

>> snub :: Ord a => [a] -> [a]
>> snub xs = f Set.empty xs where
>>     f _ [] = []
>>     f (x:xs) set
>>         | x `Set.member` set = f xs
>>         | otherwise = x:f xs (Set.insert x set)
>>
>>
>> {-# RULES "nub/snub" Ord a => forall a xs .  nub (xs::[a]) = snub xs #-}

the following compiles but i really never tested whether it works :)

{-# RULES
"freeze/IOUArray" forall (x :: (forall s e i . (Unboxed e, HasDefaultValue e) => IOUArray i e)) . freeze x = freezeIOUArray x
"thaw/IOUArray"   forall (x :: (forall   e i . (Unboxed e, HasDefaultValue e) =>   UArray i e)) . thaw   x = thawIOUArray   x
"unsafeFreeze/IOUArray" forall (x :: (forall s e i . (Unboxed e, HasDefaultValue e) => IOUArray i e)) . unsafeFreeze x = unsafeFreezeIOUArray x
"unsafeThaw/IOUArray"   forall (x :: (forall   e i . (Unboxed e, HasDefaultValue e) =>   UArray i e)) . unsafeThaw   x = unsafeThawIOUArray   x
    #-}

see http://freearc.narod.ru/ArrayRef.tar.gz for the whole story


-- 
Best regards,
 Bulat                            mailto:Bulat.Ziganshin at gmail.com



More information about the Glasgow-haskell-users mailing list