从previous question跟进后,我找到了generic-deriving包,它似乎有很多我需要的构建块。实现{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE TypeFamilies #-}
import Text.Read
import GHC.Generics
import Generics.Deriving
import Control.Lens
import Data.Default as DD
import Data.Aeson.Casing
import Data.Aeson.Types (camelTo2)
data Options = Options
{
optConstructorTagModifier :: String -> String
} deriving (Generic)
instance DD.Default Options where
def = Options
{
optConstructorTagModifier = (camelTo2 '_')
}
makeLensesWith abbreviatedFields ''Options
gEnumToString :: (ConNames (Rep a), Generic a) => Options -> a -> String
gEnumToString opt x = (opt ^. constructorTagModifier) $ conNameOf x
gEnumFromString :: forall a . (Generic a, Enum' (Rep a), ConNames (Rep a))
=> Options -> String -> Maybe a
gEnumFromString opt s = lookup s lookupTable
where
lookupTable :: [(String, a)]
lookupTable = (zipWith (,) (conNames undefined) genumDefault)
功能已减少为一行。但是,我遇到了conNames undefined
函数的问题:
ScopedTypeVariables
此代码无法编译并出现以下错误。即使我尝试使用forall a
限制 168 33 error error:
• Could not deduce (Generic a0) arising from a use of ‘conNames’
from the context: (Generic a, Enum' (Rep a), ConNames (Rep a))
bound by the type signature for:
gEnumFromString :: (Generic a, Enum' (Rep a), ConNames (Rep a)) =>
Options -> String -> Maybe a
at /Users/saurabhnanda/projects/vl-haskell/.stack-work/intero/intero784UVH.hs:(163,1)-(164,47)
The type variable ‘a0’ is ambiguous
These potential instances exist:
instance Generic (Either a b) -- Defined in ‘GHC.Generics’
instance forall a k (b :: k). Generic (Const a b)
-- Defined in ‘Data.Functor.Const’
instance Generic (Identity a) -- Defined in ‘Data.Functor.Identity’
...plus 31 others
...plus 201 instances involving out-of-scope types
(use -fprint-potential-instances to see them all)
• In the second argument of ‘zipWith’, namely
‘(conNames undefined)’
In the expression: (zipWith (,) (conNames undefined) genumDefault)
In an equation for ‘lookupTable’:
lookupTable = (zipWith (,) (conNames undefined) genumDefault) (intero)
的类型,并明确提供{{1}}(如答案中提供的建议之一所述)< / strong>即可。我做错了什么?
{{1}}
答案 0 :(得分:2)
要在范围内创建类型变量,利用扩展程序ScopedTypeVariables
,您需要显式 forall a.
。
E.g。
gEnumFromString :: forall a. (Generic a, Enum' (Rep a), ConNames (Rep a))
=> Options -> String -> Maybe a
gEnumFromString opt s = lookup s lookupTable
where
lookupTable :: [(String, a)]
lookupTable = zipWith (,) (conNames (undefined :: a)) genumDefault
没有必要重复类型约束,因为它们是&#34;携带&#34;无论如何,请a
。