Adding context to rewrite rules

2019-04-12 06:36发布

问题:

In the following code, I want to rewrite g . f as h when possible. There may be cases h hasn't got the instance of class, but I'd like to do the rewrite when it's possible. I'm getting an error message suggesting this is achievable but I'm not sure exactly what I need to change.

Here is some sample code:

{-# LANGUAGE TypeFamilies #-}

main = return ()

data D a

f :: a -> D a
f = undefined

type family T a

class G a where
  g :: D (T a) -> a

class H a where
  h :: T a -> a

{-# RULES
  "myrule" forall x. g (f x) = h x
#-}

An this is the error:

• Could not deduce (H a) arising from a use of ‘h’
  from the context: G a
    bound by the RULE "myrule" at trickyrewrite.hs:19:3-34
  Possible fix: add (H a) to the context of the RULE "myrule"
• In the expression: h x
  When checking the transformation rule "myrule"

Note the possible fix: add (H a) to the context of the RULE "myrule". This seems like it will do the job, but I'm not sure how to actually do this. a isn't even mentioned in the rule, so I'm not sure how adding H a will help when a doesn't refer to anything.

If it makes any difference, the only code I control is the class H. I can't change G. My code is of course more complex than this, but if I can see a worked example of how to get this simplified example working I should be able to work out my code I think.

Failed attempt:

I've tried @Alec's suggestion below but it doesn't seem to work, the rewrite rule isn't being triggered. Here's the code I tried:

{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeApplications #-}

module Main where

main = ((g (f (2 :: Int))) :: Char) `seq` return () 

data D a

{-# INLINE [1] f #-}
f :: a -> D a
f = undefined

type family T a
type instance T Char = Int

{-# INLINE [1] g' #-}
g' :: (G a) => D (T a) -> a
g' = undefined

class G a where
  g :: D (T a) -> a
  g = g'

instance G Char

class H a where
  h :: T a -> a

{-# RULES
  "myrule" forall (x :: H a => T a). g' (f x) = h @a x
#-}

回答1:

Normally, one can add type signatures to the variables in the forall. Something like

{-# RULES "myrule" forall (x :: H a => T a). g (f x) = h x #-}

Now, that doesn't quite work in this case because T may not be injective. Fortunately, I think TypeApplications gives us a way out of this problem by allowing us to inform GHC that the type variable a in the type T a of x is the same as the one in h:

{-# LANGUAGE TypeFamilies, TypeApplications, AllowAmbiguousTypes #-}

 ...

{-# RULES "myrule" forall (x :: H a => T a). g (f x) = h @a x #-}

We don't need to enable ScopedTypeVariables (even if we are relying on it to make sure the as are the same) because it is on by default in rewrite rules.