假设我具有以下数据类型:
data Person = Person
{ personName :: String
, personAddress :: Maybe PersonAddress
}
data PersonAddress = PersonAddress
{ personAddressStreet :: String
, personAddressStreet1 :: Maybe String
, personAddressStreet2 :: Maybe PersonAddressStreet2
}
data PersonAddressStreet2 = PersonAddressStreet2
{ personAddress2StreetStreet :: Maybe String
, personAddress2StreetNumber :: Maybe Int
}
有没有一种方法可以以通用的方式遍历
Person
类型的值并报告哪些特定字段具有Nothing
的值?理想情况下,我希望看到在嵌套结构中找到值的完整路径(例如
(Person) personAddress -> (PersonAddress) personAddressStreet1
)我研究了Typeable / Generic机器,虽然它似乎与我要尝试的工作有关,但仍不清楚如何在这里使用这些机器。
任何建议或指示将很高兴收到。
最佳答案
Generic
是实现此目的的方法。但是,您的问题中仍然存在一些歧义。我将列出这些内容,以及我假设您希望它们得到解决的方式
[String]
。每个String
表示构造函数名称或字段名称。 "no-field-name"
Nothing
字段?我将创建一个类型族,该类型族将类型映射到是否应该归入该类型。 由于此解决方案有点长,因此我将其与段落分开。
我们将从一堆导入和编译指示以及一个包含函数
nothingFields
的类开始。{-# LANGUAGE DeriveGeneric, TypeFamilies, FlexibleContexts,
MultiParamTypeClasses, TypeInType, FlexibleInstances,
TypeOperators, ScopedTypeVariables, UndecidableInstances
#-}
import GHC.Generics
import GHC.TypeLits
import Data.Proxy
-- List of constructor or field names to descend to the right field
type Field = [String]
class NothingFields a where
nothingFields :: a -> [Field]
接下来,我们将创建一个类型族,该类型族将类型映射到布尔值,表明我们是否要更深入地研究类型以查找
Nothing
字段。捕获所有默认情况(最后一个)是停止挖掘。 type family StopDigging a :: Bool where
StopDigging Person = False
StopDigging PersonAddress = False
StopDigging PersonAddressStreet2 = False
StopDigging [a] = StopDigging a
StopDigging (Maybe a) = StopDigging a
StopDigging a = True
现在,我们想要一个
NothingFields
实例和一个辅助类NothingFields'
分支,以确定是否具有我们应该尝试探索其字段的类型。注意,这是一个well-documented problem and there are tricks to solve it。-- This instance always matches because of its general instance head.
-- It dispatches to the right version of `nothingFields'` based on
-- whether the `StopDigging` type family returns true or false.
instance (flag ~ StopDigging a, NothingFields' a flag) => NothingFields a where
nothingFields = nothingFields' (Proxy :: Proxy flag)
-- Helper class whose instances' heads have different flags.
class NothingFields' a (flag :: Bool) where
nothingFields' :: proxy flag -> a -> [Field]
-- Stop digging into fields
instance NothingFields' a True where
nothingFields' _ _ = []
-- Continue digging into fields
instance (Generic a, GNothingFields' (Rep a)) => NothingFields' a False where
nothingFields' _ = gNothingFields . from
最后一个实例是通用编程开始的地方。按照惯例,我们将为此创建一个
GNothingFields'
类。在大多数情况下,为此填写实例非常简单。-- Generic helper class corresponding to `NothingFields'`
class GNothingFields' f where
gNothingFields :: f a -> [Field]
-- constructors without arguments
instance GNothingFields' U1 where
gNothingFields U1 = []
-- sum of constructors
instance (GNothingFields' f, GNothingFields' g) => GNothingFields' (f :+: g) where
gNothingFields (L1 x) = gNothingFields x
gNothingFields (R1 x) = gNothingFields x
-- product; multiple fields
instance (GNothingFields' f, GNothingFields' g) => GNothingFields' (f :*: g) where
gNothingFields (x :*: y) = gNothingFields x ++ gNothingFields y
其余情况为:字段数据的
M1
和字段中的实际数据的K1
。这才是真正的把戏发生的地方。 M1
元数据位于数据类型,构造函数和记录的周围。我们只想跟踪最后两个:-- The `D` tells us this is datatype metadata.
instance GNothingFields' f => GNothingFields' (M1 D t f) where
gNothingFields (M1 x) = gNothingFields x
-- The `C` tells us this is constructor metadata, so we extract
-- the constructor name using `symbolVal`.
instance (KnownSymbol constructor, GNothingFields' f) => GNothingFields' (M1 C ('MetaCons constructor a b) f) where
gNothingFields (M1 x) = (symbolVal (Proxy :: Proxy constructor) :) <$> gNothingFields x
-- The `S` tells us this is record field metadata, but the `Nothing`
-- tells us the field has no name.
instance (GNothingFields' f) => GNothingFields' (M1 S ('MetaSel ('Nothing) a b c) f) where
gNothingFields (M1 x) = ("no field name" :) <$> gNothingFields x
-- The `S` tells us this is record field metadata, and the `Just`
-- tells us the field has a name, so we extract that using `symbolVal`.
instance (KnownSymbol selector, GNothingFields' f) => GNothingFields' (M1 S ('MetaSel ('Just selector) a b c) f) where
gNothingFields (M1 x) = (symbolVal (Proxy :: Proxy selector) :) <$> gNothingFields x
-- This represents an actual data field of type `Maybe`. Note we
-- recurse using our initial `nothingFields` and not `gNothingFields`.
instance {-# OVERLAPPING #-} (NothingFields a) => GNothingFields' (K1 i (Maybe a)) where
gNothingFields (K1 Nothing) = [[]]
gNothingFields (K1 (Just x)) = nothingFields x
-- This represents an actual data field of type _not_ `Maybe`. Note we
-- recurse using our initial `nothingFields` and not `gNothingFields`.
instance (NothingFields a) => GNothingFields' (K1 i a) where
gNothingFields (K1 x) = nothingFields x
现在,尝试一下:
ghci> nothingFields (Person "name" Nothing)
[["Person","personAddress"]]
ghci> nothingFields (Person "name" (Just (PersonAddress "addr" Nothing Nothing)))
[["Person","personAddress","PersonAddress","personAddressStreet1"],
["Person","personAddress","PersonAddress","personAddressStreet2"]]
ghci> nothingFields (Person "name" (Just (PersonAddress "addr" (Just "street1") Nothing)))
[["Person","personAddress","PersonAddress","personAddressStreet2"]]
ghci> nothingFields (Person "name" (Just (PersonAddress "addr" Nothing (Just (PersonAddressStreet2 Nothing Nothing)))))
[["Person","personAddress","PersonAddress","personAddressStreet1"],
["Person","personAddress","PersonAddress","personAddressStreet2","PersonAddressStreet2","personAddress2StreetStreet"],
["Person","personAddress","PersonAddress","personAddressStreet2","PersonAddressStreet2","personAddress2StreetNumber"]]
免责声明
实施起来很有趣,但是您确定这确实是您想要的吗?过去,它已成为调试工具,但我不确定它是否真的有很多实用工具...总之-尽情享受吧!