haskell - 使用 generics-sop 删除特定类型的字段

标签 haskell generics

我目前正在评估 Generics.SOP 的用例,该用例涉及从给定数据类型定义派生新的相关数据类型。

我想首先定义表示 lambda 项的数据类型的“de Bruijinized”版本:

-- 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]]

要派生 Expr 的 de Bruijinized 版本,我必须删除所有 BindingOcc(然后添加一个新的 '[Int]另一种选择,但一步又一步)。 我该如何做到这一点?也许可以使用函数

-- 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

但是可惜,这并没有进行类型检查;其一,我在运行时在 deleteBindingOcc_NP 的定义中匹配 xs 的参数多态头,因此我需要一个单例编码/派生一个类型类以用于此目的定义我的小辅助函数deleteBindingOcc_NP

这里是:

-- 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

但即使这样也不起作用,因为重叠的实例不会进行类型检查:

    • 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
   |                               ^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^^

稍微思考一下,这并不奇怪:没有保证后一个类型类永远不会在其头部使用BindingOcc实例化x,我们的类型族应该删除它。所以看来基于类型类的方法并不是我想要的。

我的问题是:如何使用给定的类型签名编写deleteBindingOcc_SOP,使其能够与不同但类似相关的Code一起使用?

我担心 Code 表示作为元语言 Type 构造列表的列表可能不适合实现我想要的。不知何故,我们无法知道所有 Type 实际上都是封闭的并且不会被进一步替换。

最佳答案

也许我们可以依赖函数依赖,而不是使用类型族来关联原始类型和剥离类型:

{-# 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

这似乎有效:

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) 

具有辅助 MyC' 类而不是重叠实例的替代版本:

{-# LANGUAGE DataKinds #-}
{-# LANGUAGE AllowAmbiguousTypes #-}
import Data.Kind
import GHC.TypeLits
import Data.Type.Equality

class MyC a b | a -> b where 
  deleteBindingOcc_NP :: NP I a -> NP I b
class MyC' (isocc :: Bool)  a b | a -> b where 
  deleteBindingOcc_NP' :: NP I a -> NP I b
instance MyC '[] '[] where
  deleteBindingOcc_NP Nil = Nil
instance MyC' (x == BindingOcc) (x ': xs) ys => MyC (x ': xs) ys where
  deleteBindingOcc_NP = deleteBindingOcc_NP' @(x == BindingOcc)
instance MyC a b => MyC' True (BindingOcc ': a) b where
  deleteBindingOcc_NP' (_ :* xs) = deleteBindingOcc_NP xs
instance MyC a b => MyC' False (x ': a) (x ': b) where
  deleteBindingOcc_NP' (x :* xs) = x :* deleteBindingOcc_NP xs

关于haskell - 使用 generics-sop 删除特定类型的字段,我们在Stack Overflow上找到一个类似的问题: https://stackoverflow.com/questions/70434315/

相关文章:

haskell - 来自命令行的 GHCi 指令

haskell - 函数所有可能值的列表

haskell - 在 Frege 中创建 State 实例

C++ 类(带集合)存储通用模板类...编译问题

java - 如何检查 "multi-object"返回类型

java - 泛型方法,泛型类型未知

java - 子类化集合并使用泛型

performance - Haskell是部分应用的功能更快吗?

haskell - "Transposition"的仿函数?

arrays - 当元素是元组时扩展数组受限