Skip to content

Commit 0158eca

Browse files
committed
[#15] Add lenses for config-related types
Problem: It's quite unconvenient to access config-related records' fields by hand, especially when it comes to nested ones. Solution: Implement simple `makeLenses` function to derive lenses for an arbitrary product type and add common lenses operators & types.
1 parent 3958e21 commit 0158eca

File tree

6 files changed

+194
-1
lines changed

6 files changed

+194
-1
lines changed

core/nyan-interpolation-core.cabal

+5-1
Original file line numberDiff line numberDiff line change
@@ -4,7 +4,7 @@ cabal-version: 2.0
44
--
55
-- see: https://github.com/sol/hpack
66
--
7-
-- hash: d7bdab01e5bca79d0df2d7d3f539908dabd879f2bfc7706bd8da73a7b438387a
7+
-- hash: 4d7ed9c4a012771cadbfdbddf4b33c7474d67a1b762f4d8af7fcbb7d14ddc675
88

99
name: nyan-interpolation-core
1010
version: 0.9
@@ -34,6 +34,9 @@ library
3434
Text.Interpolation.Nyan.Core.Internal.Processor
3535
Text.Interpolation.Nyan.Core.Internal.RMode
3636
Text.Interpolation.Nyan.Core.Internal.Splice
37+
Text.Interpolation.Nyan.Lens
38+
Text.Interpolation.Nyan.Lens.TH
39+
Text.Interpolation.Nyan.Lens.Type
3740
Text.Interpolation.Nyan.RModes.Buildable
3841
Text.Interpolation.Nyan.RModes.CommonExtra
3942
Text.Interpolation.Nyan.RModes.Show
@@ -61,6 +64,7 @@ test-suite nyan-interpolation-core-tests
6164
other-modules:
6265
Test.Customization
6366
Test.Interpolator
67+
Test.Lens
6468
Test.Parser
6569
Test.Processor
6670
Test.Util

core/src/Text/Interpolation/Nyan/Core/Internal/Base.hs

+8
Original file line numberDiff line numberDiff line change
@@ -10,6 +10,8 @@ import Data.Monoid (Endo (..))
1010
import Data.Text (Text)
1111
import Language.Haskell.TH (ExpQ)
1212

13+
import Text.Interpolation.Nyan.Lens (makeLenses)
14+
1315
{- $setup
1416
1517
> import Data.Text
@@ -93,6 +95,8 @@ data SwitchesOptions = SwitchesOptions
9395
, previewLevel :: PreviewLevel
9496
} deriving stock (Show, Eq)
9597

98+
makeLenses ''SwitchesOptions
99+
96100
-- | Default switches options set in the interpolator, those that are used
97101
-- in @[int||...|]@.
98102
--
@@ -108,6 +112,8 @@ data DefaultSwitchesOptions = DefaultSwitchesOptions
108112
, defMonadic :: Maybe Bool
109113
} deriving stock (Show)
110114

115+
makeLenses ''DefaultSwitchesOptions
116+
111117
-- | Default 'DefaultSwitchesOptions'.
112118
--
113119
-- This set of switches tries to leave the text as much unmodified as possible.
@@ -175,3 +181,5 @@ data InterpolatorOptions = InterpolatorOptions
175181
-- with invisibles being marked specially (@!!@), how to update the pieces
176182
-- of text.
177183
}
184+
185+
makeLenses ''InterpolatorOptions
+52
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,52 @@
1+
-- SPDX-FileCopyrightText: 2022 Serokell <https://serokell.io/>
2+
--
3+
-- SPDX-License-Identifier: MPL-2.0
4+
5+
module Text.Interpolation.Nyan.Lens
6+
( module Text.Interpolation.Nyan.Lens.TH
7+
, module Text.Interpolation.Nyan.Lens.Type
8+
, (^.)
9+
10+
, (%~)
11+
, (%=)
12+
13+
, (.~)
14+
, (.=)
15+
16+
, (?~)
17+
, (?=)
18+
19+
, (&~)
20+
)
21+
where
22+
23+
import Control.Monad.State (MonadState, State, execState, modify)
24+
import Control.Applicative (Const(..))
25+
import Data.Functor.Identity (Identity(..))
26+
27+
import Text.Interpolation.Nyan.Lens.TH
28+
import Text.Interpolation.Nyan.Lens.Type
29+
30+
(^.) :: s -> Getting a s a -> a
31+
s ^. l = getConst $ l Const s
32+
33+
(%~) :: ASetter s t a b -> (a -> b) -> s -> t
34+
l %~ f = runIdentity . l (Identity . f)
35+
36+
(%=) :: MonadState s m => ASetter s s a b -> (a -> b) -> m ()
37+
l %= f = modify (l %~ f)
38+
39+
(.~) :: ASetter s t a b -> b -> s -> t
40+
l .~ b = runIdentity . l (const $ Identity b)
41+
42+
(.=) :: MonadState s m => ASetter s s a b -> b -> m ()
43+
l .= b = modify (l .~ b)
44+
45+
(?~) :: ASetter s t a (Maybe b) -> b -> s -> t
46+
l ?~ b = l .~ (Just b)
47+
48+
(?=) :: MonadState s m => ASetter s s a (Maybe b) -> b -> m ()
49+
l ?= b = modify (l ?~ b)
50+
51+
(&~) :: s -> State s a -> s
52+
s &~ l = execState l s
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,53 @@
1+
-- SPDX-FileCopyrightText: 2022 Serokell <https://serokell.io/>
2+
--
3+
-- SPDX-License-Identifier: MPL-2.0
4+
5+
module Text.Interpolation.Nyan.Lens.TH
6+
( makeLenses
7+
)
8+
where
9+
10+
import Control.Monad ((<=<))
11+
import Language.Haskell.TH
12+
13+
-- | Information about the record field the lenses will operate on.
14+
type RecordFieldInfo = (Name, Strict, Type)
15+
16+
-- | Given a record datatype, derives lenses for all of its fields.
17+
makeLenses :: Name -> Q [Dec]
18+
makeLenses = mapM deriveLens <=< extractRecordFields
19+
20+
extractRecordFields :: Name -> Q [RecordFieldInfo]
21+
extractRecordFields datatype = do
22+
let datatypeStr = nameBase datatype
23+
info <- reify datatype
24+
return $ case info of
25+
TyConI (DataD _ _ _ _ [RecC _ fs] _) -> fs
26+
TyConI (NewtypeD _ _ _ _ (RecC _ fs) _) -> fs
27+
TyConI (DataD _ _ _ _ [_] _) ->
28+
error $ "Can't derive lenses without record selectors: " ++ datatypeStr
29+
TyConI NewtypeD{} ->
30+
error $ "Can't derive lenses without record selectors: " ++ datatypeStr
31+
TyConI TySynD{} ->
32+
error $ "Can't derive lenses for type synonym: " ++ datatypeStr
33+
TyConI DataD{} ->
34+
error $ "Can't derive lenses for a sum type: " ++ datatypeStr
35+
_ ->
36+
error $ "Can't derive lenses for: " ++ datatypeStr
37+
++ ", type name required."
38+
39+
-- | Given a record field name,
40+
-- produces a single function declaration:
41+
-- @lensName f a = (\x -> a { field = x }) `fmap` f (field a)@
42+
deriveLens :: RecordFieldInfo -> Q Dec
43+
deriveLens (fieldName, _, _) = funD lensName [defLine]
44+
where
45+
lensName = mkName $ (nameBase fieldName) <> "L"
46+
a = mkName "a"
47+
f = mkName "f"
48+
defLine = clause pats (normalB body) []
49+
pats = [varP f, varP a]
50+
body = [| (\x -> $(record a fieldName [|x|]))
51+
`fmap` $(appE (varE f) (appE (varE fieldName) (varE a)))
52+
|]
53+
record rec fld val = val >>= \v -> recUpdE (varE rec) [return (fld, v)]
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,17 @@
1+
-- SPDX-FileCopyrightText: 2022 Serokell <https://serokell.io/>
2+
--
3+
-- SPDX-License-Identifier: MPL-2.0
4+
5+
module Text.Interpolation.Nyan.Lens.Type where
6+
7+
import Control.Applicative (Const)
8+
import Data.Functor.Identity (Identity)
9+
10+
type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t
11+
type Lens' s a = Lens s s a a
12+
13+
type ASetter s t a b = (a -> Identity b) -> s -> Identity t
14+
type ASetter' s a = ASetter s s a a
15+
16+
type Getting r s a = (a -> Const r a) -> s -> Const r s
17+
type SimpleGetter s a = forall r. Getting r s a

core/tests/Test/Lens.hs

+59
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,59 @@
1+
-- SPDX-FileCopyrightText: 2022 Serokell <https://serokell.io/>
2+
--
3+
-- SPDX-License-Identifier: MPL-2.0
4+
5+
module Test.Lens where
6+
7+
import Test.Tasty (TestTree, testGroup)
8+
import Test.Tasty.HUnit (testCase, (@?=))
9+
10+
import Text.Interpolation.Nyan.Lens
11+
12+
data Pair = Pair { first :: Int, second :: String }
13+
deriving stock (Show, Eq)
14+
15+
$(makeLenses ''Pair)
16+
17+
newtype Single = Single { value :: Maybe String }
18+
deriving stock (Show, Eq)
19+
20+
$(makeLenses ''Single)
21+
22+
test_makeLenses :: TestTree
23+
test_makeLenses = testGroup "Lenses produced by 'makeLenses' work as expected"
24+
[ testGroup "Basic lenses operators work as expected"
25+
[ testCase "(^.) operator works" do
26+
(pair ^. firstL, pair ^. secondL)
27+
@?= (100, "Hundred")
28+
29+
, testCase "(%~) operator works" do
30+
pair & (firstL %~ (+ 1)) & (secondL %~ (<> " and one"))
31+
@?= Pair 101 "Hundred and one"
32+
33+
, testCase "(.~) operator works" do
34+
pair & (firstL .~ 102) & (secondL .~ "Hundred and two")
35+
@?= Pair 102 "Hundred and two"
36+
37+
, testCase "(?~) operator works" do
38+
single & (valueL ?~ "Some value")
39+
@?= Single (Just "Some value")
40+
]
41+
42+
, testGroup "Operators leveraging 'MonadState', 'State' work as expected"
43+
[ testCase "(&~) and (.=) work" do
44+
(pair &~ do firstL .= 102)
45+
@?= Pair 102 "Hundred"
46+
47+
, testCase "(&~) and (?=) work" do
48+
(single &~ do valueL ?= "Some value")
49+
@?= Single (Just "Some value")
50+
51+
, testCase "(&~) and (%=) work" do
52+
(single &~ do valueL %= (const $ Just "Some value"))
53+
@?= Single (Just "Some value")
54+
]
55+
]
56+
where
57+
a & f = f a
58+
pair = Pair 100 "Hundred"
59+
single = Single Nothing

0 commit comments

Comments
 (0)