module Config.Lens
( key
, text
, atom
, number
, list
, values
, sections
, ann
, valuePlate
) where
import Config.Number
import Config.Value
import Data.Text
key ::
Applicative f =>
Text ->
(Value a -> f (Value a)) -> Value a -> f (Value a)
key :: Text -> (Value a -> f (Value a)) -> Value a -> f (Value a)
key i :: Text
i = ([Section a] -> f [Section a]) -> Value a -> f (Value a)
forall (f :: * -> *) a.
Applicative f =>
([Section a] -> f [Section a]) -> Value a -> f (Value a)
sections (([Section a] -> f [Section a]) -> Value a -> f (Value a))
-> ((Value a -> f (Value a)) -> [Section a] -> f [Section a])
-> (Value a -> f (Value a))
-> Value a
-> f (Value a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Section a -> f (Section a)) -> [Section a] -> f [Section a]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((Section a -> f (Section a)) -> [Section a] -> f [Section a])
-> ((Value a -> f (Value a)) -> Section a -> f (Section a))
-> (Value a -> f (Value a))
-> [Section a]
-> f [Section a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> (Value a -> f (Value a)) -> Section a -> f (Section a)
forall (f :: * -> *) a.
Applicative f =>
Text -> (Value a -> f (Value a)) -> Section a -> f (Section a)
section Text
i
section ::
Applicative f =>
Text ->
(Value a -> f (Value a)) -> Section a -> f (Section a)
section :: Text -> (Value a -> f (Value a)) -> Section a -> f (Section a)
section i :: Text
i f :: Value a -> f (Value a)
f s :: Section a
s@(Section a :: a
a j :: Text
j v :: Value a
v) | Text
i Text -> Text -> Bool
forall a. Eq a => a -> a -> Bool
== Text
j = a -> Text -> Value a -> Section a
forall a. a -> Text -> Value a -> Section a
Section a
a Text
j (Value a -> Section a) -> f (Value a) -> f (Section a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value a -> f (Value a)
f Value a
v
| Bool
otherwise = Section a -> f (Section a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Section a
s
sections :: Applicative f => ([Section a] -> f [Section a]) -> Value a -> f (Value a)
sections :: ([Section a] -> f [Section a]) -> Value a -> f (Value a)
sections f :: [Section a] -> f [Section a]
f (Sections a :: a
a xs :: [Section a]
xs) = a -> [Section a] -> Value a
forall a. a -> [Section a] -> Value a
Sections a
a ([Section a] -> Value a) -> f [Section a] -> f (Value a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Section a] -> f [Section a]
f [Section a]
xs
sections _ v :: Value a
v = Value a -> f (Value a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value a
v
text :: Applicative f => (Text -> f Text) -> Value a -> f (Value a)
text :: (Text -> f Text) -> Value a -> f (Value a)
text f :: Text -> f Text
f (Text a :: a
a t :: Text
t) = a -> Text -> Value a
forall a. a -> Text -> Value a
Text a
a (Text -> Value a) -> f Text -> f (Value a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Text -> f Text
f Text
t
text _ v :: Value a
v = Value a -> f (Value a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value a
v
atom :: Applicative f => (Atom -> f Atom) -> Value a -> f (Value a)
atom :: (Atom -> f Atom) -> Value a -> f (Value a)
atom f :: Atom -> f Atom
f (Atom a :: a
a t :: Atom
t) = a -> Atom -> Value a
forall a. a -> Atom -> Value a
Atom a
a (Atom -> Value a) -> f Atom -> f (Value a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Atom -> f Atom
f Atom
t
atom _ v :: Value a
v = Value a -> f (Value a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value a
v
number :: Applicative f => (Number -> f Number) -> Value a -> f (Value a)
number :: (Number -> f Number) -> Value a -> f (Value a)
number f :: Number -> f Number
f (Number a :: a
a n :: Number
n) = a -> Number -> Value a
forall a. a -> Number -> Value a
Number a
a (Number -> Value a) -> f Number -> f (Value a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Number -> f Number
f Number
n
number _ v :: Value a
v = Value a -> f (Value a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value a
v
list :: Applicative f => ([Value a] -> f [Value a]) -> Value a -> f (Value a)
list :: ([Value a] -> f [Value a]) -> Value a -> f (Value a)
list f :: [Value a] -> f [Value a]
f (List a :: a
a xs :: [Value a]
xs) = a -> [Value a] -> Value a
forall a. a -> [Value a] -> Value a
List a
a ([Value a] -> Value a) -> f [Value a] -> f (Value a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> [Value a] -> f [Value a]
f [Value a]
xs
list _ v :: Value a
v = Value a -> f (Value a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value a
v
valuePlate :: Applicative f => (Value a -> f (Value a)) -> Value a -> f (Value a)
valuePlate :: (Value a -> f (Value a)) -> Value a -> f (Value a)
valuePlate f :: Value a -> f (Value a)
f (List a :: a
a xs :: [Value a]
xs) = a -> [Value a] -> Value a
forall a. a -> [Value a] -> Value a
List a
a ([Value a] -> Value a) -> f [Value a] -> f (Value a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Value a -> f (Value a)) -> [Value a] -> f [Value a]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse Value a -> f (Value a)
f [Value a]
xs
valuePlate f :: Value a -> f (Value a)
f (Sections a :: a
a xs :: [Section a]
xs) = a -> [Section a] -> Value a
forall a. a -> [Section a] -> Value a
Sections a
a ([Section a] -> Value a) -> f [Section a] -> f (Value a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> (Section a -> f (Section a)) -> [Section a] -> f [Section a]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse ((Value a -> f (Value a)) -> Section a -> f (Section a)
forall (f :: * -> *) a.
Functor f =>
(Value a -> f (Value a)) -> Section a -> f (Section a)
sectionVal Value a -> f (Value a)
f) [Section a]
xs
valuePlate _ v :: Value a
v = Value a -> f (Value a)
forall (f :: * -> *) a. Applicative f => a -> f a
pure Value a
v
sectionVal :: Functor f => (Value a -> f (Value a)) -> Section a -> f (Section a)
sectionVal :: (Value a -> f (Value a)) -> Section a -> f (Section a)
sectionVal f :: Value a -> f (Value a)
f (Section a :: a
a k :: Text
k v :: Value a
v) = a -> Text -> Value a -> Section a
forall a. a -> Text -> Value a -> Section a
Section a
a Text
k (Value a -> Section a) -> f (Value a) -> f (Section a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Value a -> f (Value a)
f Value a
v
values :: Applicative f => (Value a -> f (Value a)) -> Value a -> f (Value a)
values :: (Value a -> f (Value a)) -> Value a -> f (Value a)
values = ([Value a] -> f [Value a]) -> Value a -> f (Value a)
forall (f :: * -> *) a.
Applicative f =>
([Value a] -> f [Value a]) -> Value a -> f (Value a)
list (([Value a] -> f [Value a]) -> Value a -> f (Value a))
-> ((Value a -> f (Value a)) -> [Value a] -> f [Value a])
-> (Value a -> f (Value a))
-> Value a
-> f (Value a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Value a -> f (Value a)) -> [Value a] -> f [Value a]
forall (t :: * -> *) (f :: * -> *) a b.
(Traversable t, Applicative f) =>
(a -> f b) -> t a -> f (t b)
traverse
ann :: Functor f => (a -> f a) -> Value a -> f (Value a)
ann :: (a -> f a) -> Value a -> f (Value a)
ann f :: a -> f a
f v :: Value a
v =
case Value a
v of
Sections a :: a
a x :: [Section a]
x -> (\a' :: a
a' -> a -> [Section a] -> Value a
forall a. a -> [Section a] -> Value a
Sections a
a' [Section a]
x) (a -> Value a) -> f a -> f (Value a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f a
f a
a
Number a :: a
a x :: Number
x -> (\a' :: a
a' -> a -> Number -> Value a
forall a. a -> Number -> Value a
Number a
a' Number
x) (a -> Value a) -> f a -> f (Value a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f a
f a
a
Text a :: a
a x :: Text
x -> (\a' :: a
a' -> a -> Text -> Value a
forall a. a -> Text -> Value a
Text a
a' Text
x) (a -> Value a) -> f a -> f (Value a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f a
f a
a
Atom a :: a
a x :: Atom
x -> (\a' :: a
a' -> a -> Atom -> Value a
forall a. a -> Atom -> Value a
Atom a
a' Atom
x) (a -> Value a) -> f a -> f (Value a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f a
f a
a
List a :: a
a x :: [Value a]
x -> (\a' :: a
a' -> a -> [Value a] -> Value a
forall a. a -> [Value a] -> Value a
List a
a' [Value a]
x) (a -> Value a) -> f a -> f (Value a)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> a -> f a
f a
a