{-# LANGUAGE CPP #-}
module Config.Lens
( key
, text
, number
, atom
, list
, values
, sections
) where
import Config.Value
import Data.Text
#if !MIN_VERSION_base(4,8,0)
import Control.Applicative
import Data.Traversable
#endif
key ::
Applicative f =>
Text ->
(Value -> f Value) -> Value -> f Value
key i f (Sections xs) = Sections <$> traverse (section i f) xs
key _ _ v = pure v
section ::
Applicative f =>
Text ->
(Value -> f Value) -> Section -> f Section
section i f s@(Section j v) | i == j = Section j <$> f v
| otherwise = pure s
sections :: Applicative f => ([Section] -> f [Section]) -> Value -> f Value
sections f (Sections xs) = Sections <$> f xs
sections _ v = pure v
text :: Applicative f => (Text -> f Text) -> Value -> f Value
text f (Text t) = Text <$> f t
text _ v = pure v
atom :: Applicative f => (Atom -> f Atom) -> Value -> f Value
atom f (Atom t) = Atom <$> f t
atom _ v = pure v
number :: Applicative f => (Integer -> f Integer) -> Value -> f Value
number f (Number b n) = Number b <$> f n
number _ v = pure v
list :: Applicative f => ([Value] -> f [Value]) -> Value -> f Value
list f (List xs) = List <$> f xs
list _ v = pure v
values :: Applicative f => (Value -> f Value) -> Value -> f Value
values = list . traverse