问题
If I have a record type, I can do pretty much anything I want to it with lenses. If I have a sum type, I can do pretty much whatever I want to it with prisms. But if I have a sum that includes a record, makeFields
doesn't give me lenses into the fields (of course), but only traversals for them. declarePrisms
seems a bit more promising. According to the documentation,
declarePrisms [d|
data Exp = Lit Int | Var String | Lambda{ bound::String, body::Exp }
|]
will create
data Exp = Lit Int | Var String | Lambda { bound::String, body::Exp }
_Lit :: Prism' Exp Int
_Var :: Prism' Exp String
_Lambda :: Prism' Exp (String, Exp)
This gets me almost there, but what I really want is more like this:
data Exp = Lit Int | Var String | Lambda String Exp
data LambdaRec = { _bound::String, _body::Exp }
...
_Lambda :: Prism' Exp LambdaRec
-- bound and body lenses into LambdaRec,
-- and ideally also traversals to look at them in Exp.
class MightBeLambda t where
type BoundOptic t
type BodyOptic t
bound :: BoundOptic t
body :: BodyOptic t
instance MightBeLambda Exp where
type BoundOptic Exp = Traversal' Exp String
...
instance MightBeLambda LambdaRec where
type BoundOptic LambdaRec = Lens' LambdaRec String
Is there any way to do something like this automatically, or would I have to do it by hand?
An even crazier way one might wish to do it:
data ExpTag = LitT | VarT | LambdaT
data Exp' :: ExpTag -> * where
Lit' :: Int -> Exp' LitT
Var' :: String -> Exp' VarT
Lambda' :: { _bound::String, _body::Exp } -> Exp' LambdaT
Then the prisms can be defined evilly, using unsafeCoerce
to avoid any risk of copying records.
回答1:
You can take a detour through another generated Iso to get this behavior. (makePrisms generates Isos when applied to a type with a single constructor)
{-# LANGUAGE TemplateHaskell #-}
module Demo where
import Control.Lens
data Exp = Lit Int | Var String | Lambda String Exp
data LambdaRec = LambdaRec { _bound::String, _body::Exp }
makePrisms ''Exp
makePrisms ''LambdaRec
makeLenses ''LambdaRec
_ExpLambdaRec :: Prism' Exp LambdaRec
_ExpLambdaRec = _Lambda . from _LambdaRec
-- Example using _ExpLambdaRec
expBound :: Traversal' Exp String
expBound = _ExpLambdaRec . bound
Note that thanks to optimizations that GHC can do that this intermediate record type isn't necessarily used in the generated code.
getBound :: Exp -> Maybe String
getBound = preview expBound
-- Generated core for getBound
--
-- getBound1 =
-- \ eta_B1 ->
-- case eta_B1 of _ {
-- __DEFAULT -> (Nothing) `cast` ...;
-- Lambda y1_a6XB y2_a6XC -> (Just y1_a6XB) `cast` ...
-- }
来源:https://stackoverflow.com/questions/34732588/combo-lenses-and-prisms-for-sums-of-products