我正在寻找一个函数,给定必要的返回类型,该函数将纯粹基于传递给函数的类型结构来返回与该类型匹配的产品参数部分。
例如:
data MyProduct = MyProduct String Int Bool
prod = MyProduct "yes" 0 False
func prod :: Boolean -- would return False
func prod :: String -- would return "yes"
func prod :: Double -- compiler error
同样,对于相同的功能func
,但产品不同:
data AnotherProduct = AP (Maybe Int) Char
ap = AP Nothing 'C'
func ap :: Maybe Int -- would return Nothing
是否存在这样的功能?我认为应该可以使用Generic
。我知道这在其他语言中也是可行的,例如带有Shapeless库的Scala,但是我无法确定在Haskell中如何最好地解决这一问题。
答案 0 :(得分:2)
以下是获取所有兼容字段的列表的方法:
import Data.Data
import Data.Typeable
import Data.Maybe (maybeToList)
fields :: (Data a, Typeable b) => a -> [b]
fields = gmapQr (++) [] (maybeToList . cast)
您使用的产品类型应衍生为Data
。这可以通过{-# LANGUAGE DeriveDataTypeable #-}
data MyProduct = MyProduct String Int Bool
deriving (Typeable, Data)
唯一的警告是,当您请求一个不存在的字段时,我想不出给出编译时错误的方法。我们将需要某种Data.Data
的编译时版本。我不知道有任何这样的事情,尽管我怀疑这是有可能的(尽管可能更痛苦– – deriving Data
正在为我们做很多繁重的工作!)。 / p>
答案 1 :(得分:2)
https://regex101.com/r/NWgZoH/1中提供了一种解决方案。特别是,getTyped @T :: P -> T
将访问任何产品类型T
(它是P
的实例)中类型为Generic
的字段。这是GHCi中的示例(有关更多详细信息,请参见自述文件):
> :set -XDeriveGeneric -XTypeApplications
> import Data.Generics.Product
> import GHC.Generics
> data MyProduct = MyProduct String Int Bool deriving Generic
> getTyped @Int (MyProduct "Hello" 33 True)
33
> getTyped @Int (0 :: Int, "hello")
0
答案 2 :(得分:2)
根据@ Li-yao_Xia的回答,可以使用GHC.Generics
(这是generic-lens
在幕后使用的功能)来完成此操作。 generic-lens
中的代码可能很难遵循,因此这里是从头开始的方法。
GHC.Generics
的工作方式,代表一种特定的类型,例如:
data MyProduct = MyProduct String Int Bool deriving (Generic)
通过类似如下的同构类型Rep MyProduct
:
> :kind! Rep MyProduct
Rep MyProduct :: * -> *
= D1
('MetaData "MyProduct" "GenericFetch3" "main" 'False)
(C1
('MetaCons "MyProduct" 'PrefixI 'False)
(S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 String)
:*: (S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Int)
:*: S1
('MetaSel
'Nothing 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy)
(Rec0 Bool))))
诚然,这有点疯狂,但是大多数嵌套类型都由以D1
,C1
和S1
类型表示的元数据包装组成。如果删除这些包装,则归结为:
Rep MyProduct = Rec0 String :*: Rec0 Int :*: Rec0 Bool
这有助于显示表示的结构。
无论如何,要编写一个泛型函数,您将创建一个可以处理Rep a
的类型类,该类使用实例来处理元数据包装程序以及用于表示乘积,总和等的少量类型构造函数。
在我们的例子中,我们将定义一个类型类Fetch'
,该类型类使我们能够从表示形式b
中提取类型t
的第一个值(即{{1 }}将是t
或类似的名称:
Rep MyProduct
目前,我们不要求class Fetch' t b where
fetch' :: t p -> Maybe b
实际上包含一个t
,这就是为什么我们允许b
返回fetch'
的原因。
我们需要一个实例来处理元数据:
Nothing
由于所有元数据包装器(instance Fetch' t b => Fetch' (M1 i m t) b where
fetch' (M1 x) = fetch' x
,D1
和S1
)实际上都是别名(C1
,M1 D
,M1 S
),我们可以通过一个M1 C
实例来处理所有这些问题,该实例将M1
传递给包装器。
我们还需要一种来处理产品:
fetch'
这只会从产品的左侧获取instance (Fetch' s b, Fetch' t b) => Fetch' (s :*: t) b where
fetch' (s :*: t) = fetch' s <|> fetch' t
,否则会从右侧获取b
。
我们将需要一个实例来从匹配类型(与上面的b
匹配)的(顶级)字段中提取Rec0
,因为这只是{{ 1}}):
K1 R
以及处理所有错误类型的字段的重叠全部捕获
instance Fetch' (K1 i b) b where
fetch' (K1 x) = Just x
我们还可以选择处理这些表示形式中的其他可能的类型构造函数(即instance {-# OVERLAPPABLE #-} Fetch' (K1 i b) a where
fetch' (K1 _) = Nothing
,V1
和U1
),这在下面的完整示例中已经完成。 / p>
无论如何,有了这些实例,我们可以编写:
:+:
这很正常:
fetch1 :: (Generic t, Fetch' (Rep t) b) => t -> b
fetch1 = fromJust . fetch' . from
但是与@luqui基于> fetch1 prod :: String
"yes"
> fetch1 prod :: Int
0
> fetch1 prod :: Bool
False
泛型的答案一样,它在编译时不会捕获坏字段,而是在运行时崩溃:
Data
要解决此问题,我们可以引入类型家族,该家族计算数据结构(或更确切地说是> fetch1 prod :: Double
*** Exception: Maybe.fromJust: Nothing
)是否实际包含所需的字段,如下所示:
Rep
具有类型族type family Has t b where
Has (s :*: t) b = Or (Has s b) (Has t b)
Has (K1 i b) b = 'True
Has (K1 i a) b = 'False
Has (M1 i m t) b = Has t b
的常规定义。现在,我们可以将其作为约束添加到Or
的定义中:
fetch
现在我们得到了针对错误字段的编译时错误:
fetch :: ( Generic t
, Has (Rep t) b ~ 'True
, Fetch' (Rep t) b)
=> t -> b
fetch = fromJust . fetch' . from
无论如何,将整个内容放在一起,并为所有构造函数添加实例和> fetch prod :: String
"yes"
> fetch prod :: Double
<interactive>:83:1: error:
• Couldn't match type ‘'False’ with ‘'True’
arising from a use of ‘fetch’
• In the expression: fetch prod :: Double
In an equation for ‘it’: it = fetch prod :: Double
>
定义,我们得到以下版本。请注意,对于总和类型(即Has
),它仅允许在总和中所有术语中都可以找到的字段类型(因此保证存在)。与(:+:)
中的typed
函数不同,此版本允许产品中目标类型的多个字段,而仅选择第一个字段。
generic-lens
给予:
{-# OPTIONS_GHC -Wall #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE FlexibleContexts #-}
module GenericFetch where
import Control.Applicative
import Data.Maybe
import GHC.Generics
data MyProduct = MyProduct String Int Bool deriving (Generic)
prod :: MyProduct
prod = MyProduct "yes" 0 False
data AnotherProduct = AP (Maybe Int) Char deriving (Generic)
ap :: AnotherProduct
ap = AP Nothing 'C'
data ASum = A Int String | B Int Double deriving (Generic)
asum :: ASum
asum = A 10 "hello"
class Fetch' t b where
fetch' :: t p -> Maybe b
instance Fetch' V1 b where
fetch' _ = Nothing
instance Fetch' U1 b where
fetch' _ = Nothing
instance (Fetch' s b, Fetch' t b) => Fetch' (s :+: t) b where
fetch' (L1 s) = fetch' s
fetch' (R1 t) = fetch' t
instance (Fetch' s b, Fetch' t b) => Fetch' (s :*: t) b where
fetch' (s :*: t) = fetch' s <|> fetch' t
instance Fetch' (K1 i b) b where
fetch' (K1 x) = Just x
instance {-# OVERLAPPABLE #-} Fetch' (K1 i b) a where
fetch' (K1 _) = Nothing
instance Fetch' t b => Fetch' (M1 i m t) b where
fetch' (M1 x) = fetch' x
type family Has t b where
Has V1 b = 'False
Has U1 b = 'False
Has (s :+: t) b = And (Has s b) (Has t b)
Has (s :*: t) b = Or (Has s b) (Has t b)
Has (K1 i b) b = 'True
Has (K1 i a) b = 'False
Has (M1 i m t) b = Has t b
type family Or a b where
Or 'False 'False = 'False
Or a b = 'True
type family And a b where
And 'True 'True = 'True
And a b = 'False
fetch :: ( Generic t
, Has (Rep t) b ~ 'True
, Fetch' (Rep t) b)
=> t -> b
fetch = fromJust . fetch' . from
答案 3 :(得分:0)
在Haskell 98标准下无法完成此操作。通常,参数函数无法根据其变为的具体类型来更改其行为。它必须保持通用。
关于可能要考虑这种情况的思考过程:
data MpProduct a = My Product Int Int String [a]
func
返回应该要求什么整数? a
是Char怎么办?
现在,我并不是说对具有GHC扩展知识的程序员进行一些强行破解无法实现这一目标,但是使用标准的Hindley Milner类型检查器是不可能的。