-
Notifications
You must be signed in to change notification settings - Fork 2
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
[#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.
- Loading branch information
Showing
6 changed files
with
193 additions
and
2 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,52 @@ | ||
-- SPDX-FileCopyrightText: 2022 Serokell <https://serokell.io/> | ||
-- | ||
-- SPDX-License-Identifier: MPL-2.0 | ||
|
||
module Text.Interpolation.Nyan.Lens | ||
( module Text.Interpolation.Nyan.Lens.TH | ||
, module Text.Interpolation.Nyan.Lens.Type | ||
, (^.) | ||
|
||
, (%~) | ||
, (%=) | ||
|
||
, (.~) | ||
, (.=) | ||
|
||
, (?~) | ||
, (?=) | ||
|
||
, (&~) | ||
) | ||
where | ||
|
||
import Control.Monad.State (MonadState, State, execState, modify) | ||
import Control.Applicative (Const(..)) | ||
import Data.Functor.Identity (Identity(..)) | ||
|
||
import Text.Interpolation.Nyan.Lens.TH | ||
import Text.Interpolation.Nyan.Lens.Type | ||
|
||
(^.) :: s -> Getting a s a -> a | ||
s ^. l = getConst $ l Const s | ||
|
||
(%~) :: ASetter s t a b -> (a -> b) -> s -> t | ||
l %~ f = runIdentity . l (Identity . f) | ||
|
||
(%=) :: MonadState s m => ASetter s s a b -> (a -> b) -> m () | ||
l %= f = modify (l %~ f) | ||
|
||
(.~) :: ASetter s t a b -> b -> s -> t | ||
l .~ b = runIdentity . l (const $ Identity b) | ||
|
||
(.=) :: MonadState s m => ASetter s s a b -> b -> m () | ||
l .= b = modify (l .~ b) | ||
|
||
(?~) :: ASetter s t a (Maybe b) -> b -> s -> t | ||
l ?~ b = l .~ (Just b) | ||
|
||
(?=) :: MonadState s m => ASetter s s a (Maybe b) -> b -> m () | ||
l ?= b = modify (l ?~ b) | ||
|
||
(&~) :: s -> State s a -> s | ||
s &~ l = execState l s |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,53 @@ | ||
-- SPDX-FileCopyrightText: 2022 Serokell <https://serokell.io/> | ||
-- | ||
-- SPDX-License-Identifier: MPL-2.0 | ||
|
||
module Text.Interpolation.Nyan.Lens.TH | ||
( makeLenses | ||
) | ||
where | ||
|
||
import Control.Monad ((<=<)) | ||
import Language.Haskell.TH | ||
|
||
-- | Information about the record field the lenses will operate on. | ||
type RecordFieldInfo = (Name, Strict, Type) | ||
|
||
-- | Given a record datatype, derives lenses for all of its fields. | ||
makeLenses :: Name -> Q [Dec] | ||
makeLenses = mapM deriveLens <=< extractRecordFields | ||
|
||
extractRecordFields :: Name -> Q [RecordFieldInfo] | ||
extractRecordFields datatype = do | ||
let datatypeStr = nameBase datatype | ||
info <- reify datatype | ||
return $ case info of | ||
TyConI (DataD _ _ _ _ [RecC _ fs] _) -> fs | ||
TyConI (NewtypeD _ _ _ _ (RecC _ fs) _) -> fs | ||
TyConI (DataD _ _ _ _ [_] _) -> | ||
error $ "Can't derive lenses without record selectors: " ++ datatypeStr | ||
TyConI NewtypeD{} -> | ||
error $ "Can't derive lenses without record selectors: " ++ datatypeStr | ||
TyConI TySynD{} -> | ||
error $ "Can't derive lenses for type synonym: " ++ datatypeStr | ||
TyConI DataD{} -> | ||
error $ "Can't derive lenses for a sum type: " ++ datatypeStr | ||
_ -> | ||
error $ "Can't derive lenses for: " ++ datatypeStr | ||
++ ", type name required." | ||
|
||
-- | Given a record field name, | ||
-- produces a single function declaration: | ||
-- @lensName f a = (\x -> a { field = x }) `fmap` f (field a)@ | ||
deriveLens :: RecordFieldInfo -> Q Dec | ||
deriveLens (fieldName, _, _) = funD lensName [defLine] | ||
where | ||
lensName = mkName $ (nameBase fieldName) <> "L" | ||
a = mkName "a" | ||
f = mkName "f" | ||
defLine = clause pats (normalB body) [] | ||
pats = [varP f, varP a] | ||
body = [| (\x -> $(record a fieldName [|x|])) | ||
`fmap` $(appE (varE f) (appE (varE fieldName) (varE a))) | ||
|] | ||
record rec fld val = val >>= \v -> recUpdE (varE rec) [return (fld, v)] |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,17 @@ | ||
-- SPDX-FileCopyrightText: 2022 Serokell <https://serokell.io/> | ||
-- | ||
-- SPDX-License-Identifier: MPL-2.0 | ||
|
||
module Text.Interpolation.Nyan.Lens.Type where | ||
|
||
import Control.Applicative (Const) | ||
import Data.Functor.Identity (Identity) | ||
|
||
type Lens s t a b = forall f. Functor f => (a -> f b) -> s -> f t | ||
type Lens' s a = Lens s s a a | ||
|
||
type ASetter s t a b = (a -> Identity b) -> s -> Identity t | ||
type ASetter' s a = ASetter s s a a | ||
|
||
type Getting r s a = (a -> Const r a) -> s -> Const r s | ||
type SimpleGetter s a = forall r. Getting r s a |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,59 @@ | ||
-- SPDX-FileCopyrightText: 2022 Serokell <https://serokell.io/> | ||
-- | ||
-- SPDX-License-Identifier: MPL-2.0 | ||
|
||
module Test.Lens where | ||
|
||
import Test.Tasty (TestTree, testGroup) | ||
import Test.Tasty.HUnit (testCase, (@?=)) | ||
|
||
import Text.Interpolation.Nyan.Lens | ||
|
||
data Pair = Pair { first :: Int, second :: String } | ||
deriving stock (Show, Eq) | ||
|
||
$(makeLenses ''Pair) | ||
|
||
newtype Single = Single { value :: Maybe String } | ||
deriving stock (Show, Eq) | ||
|
||
$(makeLenses ''Single) | ||
|
||
test_makeLenses :: TestTree | ||
test_makeLenses = testGroup "Lenses produced by 'makeLenses' work as expected" | ||
[ testGroup "Basic lenses operators work as expected" | ||
[ testCase "(^.) operator works" do | ||
(pair ^. firstL, pair ^. secondL) | ||
@?= (100, "Hundred") | ||
|
||
, testCase "(%~) operator works" do | ||
pair & (firstL %~ (+ 1)) & (secondL %~ (<> " and one")) | ||
@?= Pair 101 "Hundred and one" | ||
|
||
, testCase "(.~) operator works" do | ||
pair & (firstL .~ 102) & (secondL .~ "Hundred and two") | ||
@?= Pair 102 "Hundred and two" | ||
|
||
, testCase "(?~) operator works" do | ||
single & (valueL ?~ "Some value") | ||
@?= Single (Just "Some value") | ||
] | ||
|
||
, testGroup "Operators leveraging 'MonadState', 'State' work as expected" | ||
[ testCase "(&~) and (.=) work" do | ||
(pair &~ do firstL .= 102) | ||
@?= Pair 102 "Hundred" | ||
|
||
, testCase "(&~) and (?=) work" do | ||
(single &~ do valueL ?= "Some value") | ||
@?= Single (Just "Some value") | ||
|
||
, testCase "(&~) and (%=) work" do | ||
(single &~ do valueL %= (const $ Just "Some value")) | ||
@?= Single (Just "Some value") | ||
] | ||
] | ||
where | ||
a & f = f a | ||
pair = Pair 100 "Hundred" | ||
single = Single Nothing |