问题
I've encountered a problem of using Control.Lens
together with
datatypes while using the -XTypeFamilies
GHC pragma.
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}
import Control.Lens (makeLenses)
class SomeClass t where
data SomeData t :: * -> *
data MyData = MyData Int
instance SomeClass MyData where
data SomeData MyData a = SomeData {_a :: a, _b :: a}
makeLenses ''SomeData
The error message is: reifyDatatype: Use a value constructor to reify a data family instance
.
Is there any way to overcome it, maybe using some functional from Control.Lens
?
回答1:
The most sensible thing would be to just define those lenses yourself... it's not like it's very difficult:
a, b :: Lens' (SomeData MyData a) a
a = lens _a (\s a' -> s{_a=a'})
b = lens _b (\s b' -> s{_b=b'})
or even
a, b :: Functor f => (a -> f a) -> SomeData MyData a -> f (SomeData MyData a)
a f (SomeData a₀ b₀) = (`SomeData`b₀) <$> f a₀
b f (SomeData a₀ b₀) = SomeData a₀ <$> f b₀
...which doesn't use anything from the lens library at all, but is fully compatible to all lens combinators.
回答2:
tfMakeLenses
generates setters of type t a -> a -> t a
for associated datatypes.
There are some places this function can be improved, but it works!
tfMakeLenses :: Name -> DecsQ
tfMakeLenses t = do
fieldNames <- tfFieldNames t
let associatedFunNames = associateFunNames fieldNames
return (map createLens associatedFunNames)
where createLens :: (Name, Name) -> Dec
createLens (funName, fieldName) =
let dtVar = mkName "dt"
valVar = mkName "newValue"
body = NormalB (LamE [VarP valVar] (RecUpdE (VarE dtVar) [(fieldName, VarE valVar)]))
in FunD funName [(Clause [VarP dtVar] body [])]
associateFunNames :: [Name] -> [(Name, Name)]
associateFunNames [] = []
associateFunNames (fieldName:xs) = ((mkName . tail . nameBase) fieldName, (mkName . nameBase) fieldName)
: associateFunNames xs
tfFieldNames t = do
FamilyI _ ((DataInstD _ _ _ _ ((RecC _ fields):_) _):_) <- reify t
let fieldNames = flip map fields $ \(name, _, _) -> name
return fieldNames
来源:https://stackoverflow.com/questions/47946585/lenses-and-typefamilies