问题描述
我正在开发一个通用函数,以根据某些准则从复杂值中删除子值。在这里,我使用包含“ z”字母的数据构造函数删除了值。几乎可以按我的要求工作。
> genericFilter (1,[Yez,No])
Just (1,[No])
但是在特殊情况下,整个列表被删除 如果Yez是列表中的第一项。
genericFilter (1,[[Yez,No]])
Just (1,[])
>genericFilter [Yez,No,No]
nothing
调试后,我注意到:*:
中的问题。
对于:*:
的第一个参数,直接使用FilterZ(SomeZ)实例
绕过FilterZ MetaConst和Filter(K1 []),表示其余列表
使用了FilterZ MetaConst和Filter(K1 []),而没有使用FilterZ(SomeZ)!
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE NoMonomorphismRestriction #-}
{-# LANGUAGE DefaultSignatures #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE DeriveAnyClass #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE ScopedTypeVariables #-}
module Main where
import Data.Proxy
import GHC.Generics
import GHC.TypeLits
import Data.List
data SomeZ = No | Yez deriving (Show,Eq,Generic)
class FilterZ a where
gfilter :: a x -> Maybe (a x)
instance FilterZ (U1) where
gfilter U1 = Just U1
instance FilterZ (V1) where -- void
gfilter _ = nothing
instance FilterZ (K1 _1 ()) where
gfilter (K1 ()) = Just $ K1 ()
instance FilterZ (K1 _1 SomeZ) where
gfilter (K1 No) = Just $ K1 No
gfilter (K1 Yez) = nothing -- Just $ K1 Yez -- nothing
instance (FilterZ (Rep a),Show a,Generic a) => FilterZ (K1 _1 [a]) where
gfilter (K1 []) = Just $ K1 []
gfilter (K1 (h:r)) = case gfilter (from h) of
nothing -> gfilter (K1 r)
Just h' -> case gfilter (K1 r) of
nothing -> Just $ K1 [(to h') :: a] -- nothing
Just (K1 r') -> Just $ K1 ((to h') : r')
instance FilterZ (K1 _1 Int) where
gfilter (K1 n) = Just $ K1 n
instance FilterZ (K1 _1 Integer) where
gfilter (K1 n) = Just $ K1 n
instance (FilterZ a,FilterZ b) => FilterZ (a :+: b) where
gfilter (L1 x) = case gfilter x of
nothing -> nothing
Just x' -> Just $ L1 x'
gfilter (R1 x) = case gfilter x of
nothing -> nothing
Just x' -> Just $ R1 x'
instance (FilterZ a,FilterZ b) => FilterZ (a :*: b) where
gfilter (a :*: b) =
case gfilter a of
nothing -> nothing
Just a' -> case gfilter b of
nothing -> nothing
Just b' -> Just $ a' :*: b'
instance FilterZ c => FilterZ (M1 a ('MetaData dname mname pname isnewtype) c) where
gfilter (M1 x) = case gfilter x of
nothing -> nothing
Just x' -> Just $ M1 x'
instance (KNownSymbol dcn,FilterZ c) => FilterZ (M1 a ('MetaCons dcn p f) c) where
gfilter (M1 x) = case find (=='z') name of
Just _ -> nothing
nothing -> case gfilter x of
nothing -> nothing
Just x' -> Just $ M1 x'
where
name = symbolVal (undefined :: Proxy dcn)
instance FilterZ c => FilterZ (M1 a ('MetaSel fsel packness stricnesss lazines) c) where
gfilter (M1 x) = case gfilter x of
nothing -> nothing
Just x' -> Just $ M1 x'
genericFilter :: (Generic a,FilterZ (Rep a)) => a -> Maybe a
genericFilter a = fmap to $ gfilter (from a)
解决方法
函数from
仅在顶层运行。因此,如果将from
应用于列表,则会得到其通用表示形式,该通用表示形式是其头部和尾部的单位或乘积:
*Gen> from [Yez,No]
M1 {unM1 = R1 (M1 {unM1 = M1 {unM1 = K1 {unK1 = Yez}} :*: M1 {unM1 = K1 {unK1 = [No]}}})}
请注意,磁头是分开的,但是[No]
没有进一步分解。因此,如果您的列表不在最高级别,则它永远不会像这样在from
下分解:
*Gen> from (1,[Yez,No])
M1 {unM1 = M1 {unM1 = M1 {unM1 = K1 {unK1 = 1}} :*: M1 {unM1 = K1 {unK1 = [Yez,No]}}}}
请注意,列表[Yez,No]
保持不变。
在第一种情况下,genericFilter
经过M1
并到达:*:
。产品的第一个组件是Yez
,因此通过FilterZ (K1 _1 SomeZ)
实例将其映射到Nothing
。 (FilterZ a,FilterZ b) => FilterZ (a :*: b)
实例说最终结果应该是Nothing
。
在第二种情况下,genericFilter
再次经过M1
并到达:*:。这次,第一个组件是一个单元,该单元映射到该单元,第二个组件是[SomeZ]
类型,并由(FilterZ (Rep a),Show a,Generic a) => FilterZ (K1 _1 [a])
实例过滤。