I'm currently evaluating Generics.SOP
for a use case involving derivation of new, related data types from a given data type definition.
I want to start out by defining a "de Bruijinized" version of a data type representing lambda terms:
-- The reproducer needs only some of the LANGUAGE pragmas and imports,
-- but it might be convenient for your (or my) solutions
{-# LANGUAGE GeneralisedNewtypeDeriving #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE TemplateHaskell #-}
module SOP where
import Data.SOP.NS
import Generics.SOP
import Generics.SOP.TH
import Data.Kind
newtype Var = V String
deriving (Eq, Ord, Show)
newtype BindingOcc = B Var
deriving (Eq, Ord, Show)
data Expr
= Var Var
| App Expr Expr
| Lam BindingOcc Expr
deriveGeneric ''Expr -- Code Expr = '[ '[Var], '[Expr, Expr], '[BindingOcc, Expr]]
To derive the de Bruijinized version of Expr
, I have to delete all BindingOcc
s (and afterwards add a new '[Int]
alternative, but one step after another). How do I do that? Perhaps with a function
-- Let's be absolutely explicit about it and inline `Code`
-- Also don't want to confuse the type-checker with a type
-- family that removes the field just yet
deleteBindingOcc_SOP :: SOP I '[ '[Var], '[Expr, Expr], '[BindingOcc, Expr]]
-> SOP I '[ '[Var], '[Expr, Expr], '[Expr]]
deleteBindingOcc_SOP arg = SOP $ trans_NS Proxy {- will be filled in below -} deleteBindingOcc_NP (unSOP arg)
deleteBindingOcc_NP :: NP I xs -> NP I (WithoutBindingOccs xs)
deleteBindingOcc_NP Nil = Nil
deleteBindingOcc_NP (x :* xs)
| B _ <- x = deleteBindingOcc_NP xs
| otherwise = x :* deleteBindingOcc_NP xs
-- I guess I expected to write the following type family
type family WithoutBindingOcc (xs :: [Type]) :: [Type] where
WithoutBindingOcc '[] = '[]
WithoutBindingOcc (BindingOcc ': xs) = WithoutBindingOcc xs
WithoutBindingOcc (x ': xs) = x ': WithoutBindingOcc xs
But alas, that doesn't type-check; for one, I match on the parametrically-polymorphic head of xs
at runtime in the definition of deleteBindingOcc_NP
, so I need a singleton encoding/derive a type class just for the purpose of defining my little helper function deleteBindingOcc_NP
.
Here it is:
-- Now we know the full type of the proxy, carrying the constraint that `deleteBindingOcc_NP` wants
deleteBindingOcc_SOP arg = SOP $ trans_NS (Proxy :: Proxy MyC) deleteBindingOcc_NP (unSOP arg)
class b ~ WithoutBindingOcc a => MyC a b where -- welp
deleteBindingOcc_NP :: NP I a -> NP I b
instance MyC '[] '[] where
deleteBindingOcc_NP Nil = Nil
instance {-# OVERLAPPING #-} MyC a b => MyC (BindingOcc ': a) b where
deleteBindingOcc_NP (_ :* xs) = deleteBindingOcc_NP xs
instance {-# OVERLAPPABLE #-} MyC a b => MyC (x ': a) (x ': b) where
deleteBindingOcc_NP (x :* xs) = x :* deleteBindingOcc_NP xs
But even that doesn't work, because the overlapped instance won't type-check:
• Could not deduce: WithoutBindingOcc (x : a) ~ (x : b)
arising from the superclasses of an instance declaration
from the context: MyC a b
bound by the instance declaration at SOP2.hs:52:31-62
• In the instance declaration for ‘MyC (x : a) (x : b)’
|
52 | instance {-# OVERLAPPABLE #-} MyC a b => MyC (x ': a) (x ': b) where
| ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^
And upon thinking about it a bit, that is not surprising: There is no guarantee that the latter type class is never instantiated with a BindingOcc
at its head x
, which our type family should remove. So it appears that a type class based approach is not what I want here.
My question is: How do write deleteBindingOcc_SOP
with the given type signature in a manner that it works with different, but similarly related Code
s?
I fear that the Code
representation as a list of list of meta-language Type
constructs may not be suitable to achieve what I want. Somehow we can't know that all the Type
s are in fact closed and won't be substituted any further.
CodePudding user response:
I have no idea whether what you're doing is a good idea ...
But all that aside, here is something that works for at least your simple use case.
type family Equal (a :: k) (b :: k) :: Bool where
Equal a a = True
Equal _ _ = False
type family IfThenElse (b :: Bool) (t :: a) (e :: a) where
IfThenElse True t _ = t
IfThenElse False _ e = e
class CanDecide (b :: Bool) where
ifthenelse :: Proxy b -> ((b ~ True) => r) -> ((b ~ False) => r) -> r
instance CanDecide True where ifthenelse _ x _ = x
instance CanDecide False where ifthenelse _ _ y = y
class CanDecide (Equal a BindingOcc) => IsBindingOcc a
instance CanDecide (Equal a BindingOcc) => IsBindingOcc a
type family DeleteBindingOcc (xs :: [Type]) :: [Type] where
DeleteBindingOcc '[] = '[]
DeleteBindingOcc (x : xs) = IfThenElse (Equal x BindingOcc) (DeleteBindingOcc xs) (x : DeleteBindingOcc xs)
class (All IsBindingOcc xs, DeleteBindingOcc xs ~ ys) => RelDeleteBindingOcc xs ys
instance (All IsBindingOcc xs, DeleteBindingOcc xs ~ ys) => RelDeleteBindingOcc xs ys
deleteBindingOcc_NP :: RelDeleteBindingOcc xs ys => NP f xs -> NP f ys
deleteBindingOcc_NP Nil = Nil
deleteBindingOcc_NP ((x :: f x) :* xs) =
let
ys = deleteBindingOcc_NP xs
in
ifthenelse (Proxy @(Equal x BindingOcc)) ys (x :* ys)
deleteBindingOcc_SOP :: SOP I '[ '[Var], '[Expr, Expr], '[BindingOcc, Expr]]
-> SOP I '[ '[Var], '[Expr, Expr], '[Expr]]
deleteBindingOcc_SOP arg = SOP $ trans_NS (Proxy @RelDeleteBindingOcc) deleteBindingOcc_NP (unSOP arg)
BTW, there is a nice-looking library called generic-data-surgery (that I unfortunately never used myself) that claims to be good at this kind of thing.
CodePudding user response:
Instead of using a type family to relate the original and stripped types, perhaps we could rely on a functional dependency:
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE UndecidableInstances #-} -- required by some of the magic below
{-# LANGUAGE TypeApplications #-}
class MyC a b | a -> b where
deleteBindingOcc_NP :: NP I a -> NP I b
instance MyC '[] '[] where
deleteBindingOcc_NP Nil = Nil
instance {-# OVERLAPPING #-} MyC a b => MyC (BindingOcc ': a) b where
deleteBindingOcc_NP (_ :* xs) = deleteBindingOcc_NP xs
instance {-# OVERLAPPABLE #-} MyC a b => MyC (x ': a) (x ': b) where
deleteBindingOcc_NP (x :* xs) = x :* deleteBindingOcc_NP xs
This seems to work:
deleteBindingOcc_SOP :: SOP I '[ '[Var], '[Expr, Expr], '[BindingOcc, Expr]]
-> SOP I '[ '[Var], '[Expr, Expr], '[Expr]]
deleteBindingOcc_SOP arg = SOP $ trans_NS (Proxy @MyC) deleteBindingOcc_NP (unSOP arg)