{-# LANGUAGE DataKinds #-}
module Codec.CBOR.Cuddle.Huddle.Optics (commentL, nameL) where
import Codec.CBOR.Cuddle.Huddle
import Data.Generics.Product (HasField' (field'))
import Data.Text qualified as T
import Optics.Core
mcommentL ::
HasField' "description" a (Maybe T.Text) =>
Lens a a (Maybe T.Text) (Maybe T.Text)
= forall (field :: Symbol) s a. HasField' field s a => Lens s s a a
field' @"description"
commentL ::
HasField' "description" a (Maybe T.Text) =>
AffineTraversal a a T.Text T.Text
= Lens a a (Maybe Text) (Maybe Text)
forall a.
HasField' "description" a (Maybe Text) =>
Lens a a (Maybe Text) (Maybe Text)
mcommentL Lens a a (Maybe Text) (Maybe Text)
-> Optic A_Prism NoIx (Maybe Text) (Maybe Text) Text Text
-> Optic An_AffineTraversal NoIx a a Text Text
forall k l m (is :: IxList) (js :: IxList) (ks :: IxList) s t u v a
b.
(JoinKinds k l m, AppendIndices is js ks) =>
Optic k is s t u v -> Optic l js u v a b -> Optic m ks s t a b
% Optic A_Prism NoIx (Maybe Text) (Maybe Text) Text Text
forall a b. Prism (Maybe a) (Maybe b) a b
_Just
nameL :: Lens (Named a) (Named a) T.Text T.Text
nameL :: forall a. Lens (Named a) (Named a) Text Text
nameL = forall (field :: Symbol) s a. HasField' field s a => Lens s s a a
field' @"name"