Je suis en train de développer une fonction générique pour enlever une sous-valeur d'une valeur complexe en fonction de certains critères. Ici, je supprime les valeurs avec le constructeur de données contenant la lettre "z". Cela fonctionne presque comme je le souhaite.
> genericFilter (1,[Yez, No])
Just (1,[No])
Mais il y a un cas spécial où la liste entière est abandonnée. si Yez est le premier élément de la liste.
genericFilter (1,[[Yez, No]])
Just (1,[])
>genericFilter [Yez, No, No]
Nothing
Après le débogage, j'ai remarqué que le problème en :*:
. Pour le premier argument de :*:
L'instance FilterZ (SomeZ) est utilisée directement. en contournant FilterZ MetaConst et Filter (K1 []), alors que pour le reste de la liste FilterZ MetaConst et Filter (K1 []) sont utilisés et FilterZ (SomeZ) ne l'est pas !
{-# 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)