{-# Language DeriveGeneric, DeriveTraversable, DeriveDataTypeable #-}

-- | This module provides the types used in this package for configuration.
-- Visit "Config.Parser" to parse values of this type in a convenient
-- layout based notation.
module Config.Value
  ( Section(..)
  , Value(..)
  , Atom(..)
  , valueAnn
  ) where

import Data.Text    (Text)
import Data.Data    (Data, Typeable)
import Data.String  (IsString(..))
import GHC.Generics (Generic, Generic1)

import Config.Number (Number)

-- | A single section of a 'Value'
--
-- Example:
--
--    * @my-key: my-value@ is @'Section' _ "my-key" ('Atom' _ "my-value")@
data Section a = Section
  { Section a -> a
sectionAnn   :: a
  , Section a -> Text
sectionName  :: Text
  , Section a -> Value a
sectionValue :: Value a
  }
  deriving ( Section a -> Section a -> Bool
(Section a -> Section a -> Bool)
-> (Section a -> Section a -> Bool) -> Eq (Section a)
forall a. Eq a => Section a -> Section a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Section a -> Section a -> Bool
$c/= :: forall a. Eq a => Section a -> Section a -> Bool
== :: Section a -> Section a -> Bool
$c== :: forall a. Eq a => Section a -> Section a -> Bool
Eq, ReadPrec [Section a]
ReadPrec (Section a)
Int -> ReadS (Section a)
ReadS [Section a]
(Int -> ReadS (Section a))
-> ReadS [Section a]
-> ReadPrec (Section a)
-> ReadPrec [Section a]
-> Read (Section a)
forall a. Read a => ReadPrec [Section a]
forall a. Read a => ReadPrec (Section a)
forall a. Read a => Int -> ReadS (Section a)
forall a. Read a => ReadS [Section a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Section a]
$creadListPrec :: forall a. Read a => ReadPrec [Section a]
readPrec :: ReadPrec (Section a)
$creadPrec :: forall a. Read a => ReadPrec (Section a)
readList :: ReadS [Section a]
$creadList :: forall a. Read a => ReadS [Section a]
readsPrec :: Int -> ReadS (Section a)
$creadsPrec :: forall a. Read a => Int -> ReadS (Section a)
Read, Int -> Section a -> ShowS
[Section a] -> ShowS
Section a -> String
(Int -> Section a -> ShowS)
-> (Section a -> String)
-> ([Section a] -> ShowS)
-> Show (Section a)
forall a. Show a => Int -> Section a -> ShowS
forall a. Show a => [Section a] -> ShowS
forall a. Show a => Section a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Section a] -> ShowS
$cshowList :: forall a. Show a => [Section a] -> ShowS
show :: Section a -> String
$cshow :: forall a. Show a => Section a -> String
showsPrec :: Int -> Section a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Section a -> ShowS
Show, Typeable, Typeable (Section a)
DataType
Constr
Typeable (Section a)
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Section a -> c (Section a))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (Section a))
-> (Section a -> Constr)
-> (Section a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c (Section a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e))
    -> Maybe (c (Section a)))
-> ((forall b. Data b => b -> b) -> Section a -> Section a)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Section a -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Section a -> r)
-> (forall u. (forall d. Data d => d -> u) -> Section a -> [u])
-> (forall u.
    Int -> (forall d. Data d => d -> u) -> Section a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Section a -> m (Section a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Section a -> m (Section a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Section a -> m (Section a))
-> Data (Section a)
Section a -> DataType
Section a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (Section a))
(forall b. Data b => b -> b) -> Section a -> Section a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Section a -> c (Section a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Section a)
forall a. Data a => Typeable (Section a)
forall a. Data a => Section a -> DataType
forall a. Data a => Section a -> Constr
forall a.
Data a =>
(forall b. Data b => b -> b) -> Section a -> Section a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> Section a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> Section a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Section a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Section a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Section a -> m (Section a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Section a -> m (Section a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Section a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Section a -> c (Section a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Section a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Section a))
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Section a -> u
forall u. (forall d. Data d => d -> u) -> Section a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Section a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Section a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Section a -> m (Section a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Section a -> m (Section a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Section a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Section a -> c (Section a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Section a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Section a))
$cSection :: Constr
$tSection :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Section a -> m (Section a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Section a -> m (Section a)
gmapMp :: (forall d. Data d => d -> m d) -> Section a -> m (Section a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Section a -> m (Section a)
gmapM :: (forall d. Data d => d -> m d) -> Section a -> m (Section a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Section a -> m (Section a)
gmapQi :: Int -> (forall d. Data d => d -> u) -> Section a -> u
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> Section a -> u
gmapQ :: (forall d. Data d => d -> u) -> Section a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> Section a -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Section a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Section a -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Section a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Section a -> r
gmapT :: (forall b. Data b => b -> b) -> Section a -> Section a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> Section a -> Section a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Section a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (Section a))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (Section a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Section a))
dataTypeOf :: Section a -> DataType
$cdataTypeOf :: forall a. Data a => Section a -> DataType
toConstr :: Section a -> Constr
$ctoConstr :: forall a. Data a => Section a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Section a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Section a)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Section a -> c (Section a)
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Section a -> c (Section a)
$cp1Data :: forall a. Data a => Typeable (Section a)
Data
           , a -> Section b -> Section a
(a -> b) -> Section a -> Section b
(forall a b. (a -> b) -> Section a -> Section b)
-> (forall a b. a -> Section b -> Section a) -> Functor Section
forall a b. a -> Section b -> Section a
forall a b. (a -> b) -> Section a -> Section b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Section b -> Section a
$c<$ :: forall a b. a -> Section b -> Section a
fmap :: (a -> b) -> Section a -> Section b
$cfmap :: forall a b. (a -> b) -> Section a -> Section b
Functor, Section a -> Bool
(a -> m) -> Section a -> m
(a -> b -> b) -> b -> Section a -> b
(forall m. Monoid m => Section m -> m)
-> (forall m a. Monoid m => (a -> m) -> Section a -> m)
-> (forall m a. Monoid m => (a -> m) -> Section a -> m)
-> (forall a b. (a -> b -> b) -> b -> Section a -> b)
-> (forall a b. (a -> b -> b) -> b -> Section a -> b)
-> (forall b a. (b -> a -> b) -> b -> Section a -> b)
-> (forall b a. (b -> a -> b) -> b -> Section a -> b)
-> (forall a. (a -> a -> a) -> Section a -> a)
-> (forall a. (a -> a -> a) -> Section a -> a)
-> (forall a. Section a -> [a])
-> (forall a. Section a -> Bool)
-> (forall a. Section a -> Int)
-> (forall a. Eq a => a -> Section a -> Bool)
-> (forall a. Ord a => Section a -> a)
-> (forall a. Ord a => Section a -> a)
-> (forall a. Num a => Section a -> a)
-> (forall a. Num a => Section a -> a)
-> Foldable Section
forall a. Eq a => a -> Section a -> Bool
forall a. Num a => Section a -> a
forall a. Ord a => Section a -> a
forall m. Monoid m => Section m -> m
forall a. Section a -> Bool
forall a. Section a -> Int
forall a. Section a -> [a]
forall a. (a -> a -> a) -> Section a -> a
forall m a. Monoid m => (a -> m) -> Section a -> m
forall b a. (b -> a -> b) -> b -> Section a -> b
forall a b. (a -> b -> b) -> b -> Section a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: Section a -> a
$cproduct :: forall a. Num a => Section a -> a
sum :: Section a -> a
$csum :: forall a. Num a => Section a -> a
minimum :: Section a -> a
$cminimum :: forall a. Ord a => Section a -> a
maximum :: Section a -> a
$cmaximum :: forall a. Ord a => Section a -> a
elem :: a -> Section a -> Bool
$celem :: forall a. Eq a => a -> Section a -> Bool
length :: Section a -> Int
$clength :: forall a. Section a -> Int
null :: Section a -> Bool
$cnull :: forall a. Section a -> Bool
toList :: Section a -> [a]
$ctoList :: forall a. Section a -> [a]
foldl1 :: (a -> a -> a) -> Section a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Section a -> a
foldr1 :: (a -> a -> a) -> Section a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> Section a -> a
foldl' :: (b -> a -> b) -> b -> Section a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Section a -> b
foldl :: (b -> a -> b) -> b -> Section a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Section a -> b
foldr' :: (a -> b -> b) -> b -> Section a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Section a -> b
foldr :: (a -> b -> b) -> b -> Section a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> Section a -> b
foldMap' :: (a -> m) -> Section a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Section a -> m
foldMap :: (a -> m) -> Section a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Section a -> m
fold :: Section m -> m
$cfold :: forall m. Monoid m => Section m -> m
Foldable, Functor Section
Foldable Section
Functor Section
-> Foldable Section
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> Section a -> f (Section b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    Section (f a) -> f (Section a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> Section a -> m (Section b))
-> (forall (m :: * -> *) a.
    Monad m =>
    Section (m a) -> m (Section a))
-> Traversable Section
(a -> f b) -> Section a -> f (Section b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => Section (m a) -> m (Section a)
forall (f :: * -> *) a.
Applicative f =>
Section (f a) -> f (Section a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Section a -> m (Section b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Section a -> f (Section b)
sequence :: Section (m a) -> m (Section a)
$csequence :: forall (m :: * -> *) a. Monad m => Section (m a) -> m (Section a)
mapM :: (a -> m b) -> Section a -> m (Section b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Section a -> m (Section b)
sequenceA :: Section (f a) -> f (Section a)
$csequenceA :: forall (f :: * -> *) a.
Applicative f =>
Section (f a) -> f (Section a)
traverse :: (a -> f b) -> Section a -> f (Section b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Section a -> f (Section b)
$cp2Traversable :: Foldable Section
$cp1Traversable :: Functor Section
Traversable
           , (forall x. Section a -> Rep (Section a) x)
-> (forall x. Rep (Section a) x -> Section a)
-> Generic (Section a)
forall x. Rep (Section a) x -> Section a
forall x. Section a -> Rep (Section a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (Section a) x -> Section a
forall a x. Section a -> Rep (Section a) x
$cto :: forall a x. Rep (Section a) x -> Section a
$cfrom :: forall a x. Section a -> Rep (Section a) x
Generic, (forall a. Section a -> Rep1 Section a)
-> (forall a. Rep1 Section a -> Section a) -> Generic1 Section
forall a. Rep1 Section a -> Section a
forall a. Section a -> Rep1 Section a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cto1 :: forall a. Rep1 Section a -> Section a
$cfrom1 :: forall a. Section a -> Rep1 Section a
Generic1
           )

-- | Wrapper to distinguish 'Atom' from 'Text' by
-- type in a configuration. Atoms can be constructed
-- using the @OverloadedStrings@ extension.
newtype Atom = MkAtom { Atom -> Text
atomName :: Text }
  deriving ( Atom -> Atom -> Bool
(Atom -> Atom -> Bool) -> (Atom -> Atom -> Bool) -> Eq Atom
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Atom -> Atom -> Bool
$c/= :: Atom -> Atom -> Bool
== :: Atom -> Atom -> Bool
$c== :: Atom -> Atom -> Bool
Eq, Eq Atom
Eq Atom
-> (Atom -> Atom -> Ordering)
-> (Atom -> Atom -> Bool)
-> (Atom -> Atom -> Bool)
-> (Atom -> Atom -> Bool)
-> (Atom -> Atom -> Bool)
-> (Atom -> Atom -> Atom)
-> (Atom -> Atom -> Atom)
-> Ord Atom
Atom -> Atom -> Bool
Atom -> Atom -> Ordering
Atom -> Atom -> Atom
forall a.
Eq a
-> (a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Atom -> Atom -> Atom
$cmin :: Atom -> Atom -> Atom
max :: Atom -> Atom -> Atom
$cmax :: Atom -> Atom -> Atom
>= :: Atom -> Atom -> Bool
$c>= :: Atom -> Atom -> Bool
> :: Atom -> Atom -> Bool
$c> :: Atom -> Atom -> Bool
<= :: Atom -> Atom -> Bool
$c<= :: Atom -> Atom -> Bool
< :: Atom -> Atom -> Bool
$c< :: Atom -> Atom -> Bool
compare :: Atom -> Atom -> Ordering
$ccompare :: Atom -> Atom -> Ordering
$cp1Ord :: Eq Atom
Ord, Int -> Atom -> ShowS
[Atom] -> ShowS
Atom -> String
(Int -> Atom -> ShowS)
-> (Atom -> String) -> ([Atom] -> ShowS) -> Show Atom
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Atom] -> ShowS
$cshowList :: [Atom] -> ShowS
show :: Atom -> String
$cshow :: Atom -> String
showsPrec :: Int -> Atom -> ShowS
$cshowsPrec :: Int -> Atom -> ShowS
Show, ReadPrec [Atom]
ReadPrec Atom
Int -> ReadS Atom
ReadS [Atom]
(Int -> ReadS Atom)
-> ReadS [Atom] -> ReadPrec Atom -> ReadPrec [Atom] -> Read Atom
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Atom]
$creadListPrec :: ReadPrec [Atom]
readPrec :: ReadPrec Atom
$creadPrec :: ReadPrec Atom
readList :: ReadS [Atom]
$creadList :: ReadS [Atom]
readsPrec :: Int -> ReadS Atom
$creadsPrec :: Int -> ReadS Atom
Read, Typeable, Typeable Atom
DataType
Constr
Typeable Atom
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Atom -> c Atom)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Atom)
-> (Atom -> Constr)
-> (Atom -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Atom))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Atom))
-> ((forall b. Data b => b -> b) -> Atom -> Atom)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Atom -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Atom -> r)
-> (forall u. (forall d. Data d => d -> u) -> Atom -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Atom -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Atom -> m Atom)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Atom -> m Atom)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Atom -> m Atom)
-> Data Atom
Atom -> DataType
Atom -> Constr
(forall b. Data b => b -> b) -> Atom -> Atom
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Atom -> c Atom
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Atom
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Atom -> u
forall u. (forall d. Data d => d -> u) -> Atom -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Atom -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Atom -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Atom -> m Atom
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Atom -> m Atom
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Atom
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Atom -> c Atom
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Atom)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Atom)
$cMkAtom :: Constr
$tAtom :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Atom -> m Atom
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Atom -> m Atom
gmapMp :: (forall d. Data d => d -> m d) -> Atom -> m Atom
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Atom -> m Atom
gmapM :: (forall d. Data d => d -> m d) -> Atom -> m Atom
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Atom -> m Atom
gmapQi :: Int -> (forall d. Data d => d -> u) -> Atom -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Atom -> u
gmapQ :: (forall d. Data d => d -> u) -> Atom -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Atom -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Atom -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Atom -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Atom -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Atom -> r
gmapT :: (forall b. Data b => b -> b) -> Atom -> Atom
$cgmapT :: (forall b. Data b => b -> b) -> Atom -> Atom
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Atom)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Atom)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Atom)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Atom)
dataTypeOf :: Atom -> DataType
$cdataTypeOf :: Atom -> DataType
toConstr :: Atom -> Constr
$ctoConstr :: Atom -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Atom
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Atom
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Atom -> c Atom
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Atom -> c Atom
$cp1Data :: Typeable Atom
Data
           , (forall x. Atom -> Rep Atom x)
-> (forall x. Rep Atom x -> Atom) -> Generic Atom
forall x. Rep Atom x -> Atom
forall x. Atom -> Rep Atom x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Atom x -> Atom
$cfrom :: forall x. Atom -> Rep Atom x
Generic
           )

instance IsString Atom where
  fromString :: String -> Atom
fromString = Text -> Atom
MkAtom (Text -> Atom) -> (String -> Text) -> String -> Atom
forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
forall a. IsString a => String -> a
fromString

-- | Sum type of the values supported by this language.
--
-- 'Value' is parameterized over an annotation type indented to be used for
-- file position or other application specific information. When no
-- annotations are needed, '()' is a fine choice.
data Value a
  = Sections a [Section a] -- ^ lists of key-value pairs
  | Number   a Number      -- ^ numbers
  | Text     a Text        -- ^ quoted strings
  | Atom     a Atom        -- ^ unquoted strings
  | List     a [Value a]   -- ^ lists
  deriving ( Value a -> Value a -> Bool
(Value a -> Value a -> Bool)
-> (Value a -> Value a -> Bool) -> Eq (Value a)
forall a. Eq a => Value a -> Value a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Value a -> Value a -> Bool
$c/= :: forall a. Eq a => Value a -> Value a -> Bool
== :: Value a -> Value a -> Bool
$c== :: forall a. Eq a => Value a -> Value a -> Bool
Eq, ReadPrec [Value a]
ReadPrec (Value a)
Int -> ReadS (Value a)
ReadS [Value a]
(Int -> ReadS (Value a))
-> ReadS [Value a]
-> ReadPrec (Value a)
-> ReadPrec [Value a]
-> Read (Value a)
forall a. Read a => ReadPrec [Value a]
forall a. Read a => ReadPrec (Value a)
forall a. Read a => Int -> ReadS (Value a)
forall a. Read a => ReadS [Value a]
forall a.
(Int -> ReadS a)
-> ReadS [a] -> ReadPrec a -> ReadPrec [a] -> Read a
readListPrec :: ReadPrec [Value a]
$creadListPrec :: forall a. Read a => ReadPrec [Value a]
readPrec :: ReadPrec (Value a)
$creadPrec :: forall a. Read a => ReadPrec (Value a)
readList :: ReadS [Value a]
$creadList :: forall a. Read a => ReadS [Value a]
readsPrec :: Int -> ReadS (Value a)
$creadsPrec :: forall a. Read a => Int -> ReadS (Value a)
Read, Int -> Value a -> ShowS
[Value a] -> ShowS
Value a -> String
(Int -> Value a -> ShowS)
-> (Value a -> String) -> ([Value a] -> ShowS) -> Show (Value a)
forall a. Show a => Int -> Value a -> ShowS
forall a. Show a => [Value a] -> ShowS
forall a. Show a => Value a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Value a] -> ShowS
$cshowList :: forall a. Show a => [Value a] -> ShowS
show :: Value a -> String
$cshow :: forall a. Show a => Value a -> String
showsPrec :: Int -> Value a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Value a -> ShowS
Show, Typeable, Typeable (Value a)
DataType
Constr
Typeable (Value a)
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> Value a -> c (Value a))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (Value a))
-> (Value a -> Constr)
-> (Value a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c (Value a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Value a)))
-> ((forall b. Data b => b -> b) -> Value a -> Value a)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> Value a -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> Value a -> r)
-> (forall u. (forall d. Data d => d -> u) -> Value a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Value a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Value a -> m (Value a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Value a -> m (Value a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Value a -> m (Value a))
-> Data (Value a)
Value a -> DataType
Value a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (Value a))
(forall b. Data b => b -> b) -> Value a -> Value a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Value a -> c (Value a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Value a)
forall a. Data a => Typeable (Value a)
forall a. Data a => Value a -> DataType
forall a. Data a => Value a -> Constr
forall a.
Data a =>
(forall b. Data b => b -> b) -> Value a -> Value a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> Value a -> u
forall a u.
Data a =>
(forall d. Data d => d -> u) -> Value a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Value a -> r
forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Value a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Value a -> m (Value a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Value a -> m (Value a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Value a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Value a -> c (Value a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Value a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Value a))
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Value a -> u
forall u. (forall d. Data d => d -> u) -> Value a -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Value a -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Value a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Value a -> m (Value a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Value a -> m (Value a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Value a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Value a -> c (Value a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (Value a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Value a))
$cList :: Constr
$cAtom :: Constr
$cText :: Constr
$cNumber :: Constr
$cSections :: Constr
$tValue :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Value a -> m (Value a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Value a -> m (Value a)
gmapMp :: (forall d. Data d => d -> m d) -> Value a -> m (Value a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> Value a -> m (Value a)
gmapM :: (forall d. Data d => d -> m d) -> Value a -> m (Value a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> Value a -> m (Value a)
gmapQi :: Int -> (forall d. Data d => d -> u) -> Value a -> u
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> Value a -> u
gmapQ :: (forall d. Data d => d -> u) -> Value a -> [u]
$cgmapQ :: forall a u.
Data a =>
(forall d. Data d => d -> u) -> Value a -> [u]
gmapQr :: (r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Value a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Value a -> r
gmapQl :: (r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Value a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Value a -> r
gmapT :: (forall b. Data b => b -> b) -> Value a -> Value a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> Value a -> Value a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Value a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Value a))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (Value a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (Value a))
dataTypeOf :: Value a -> DataType
$cdataTypeOf :: forall a. Data a => Value a -> DataType
toConstr :: Value a -> Constr
$ctoConstr :: forall a. Data a => Value a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Value a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (Value a)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Value a -> c (Value a)
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Value a -> c (Value a)
$cp1Data :: forall a. Data a => Typeable (Value a)
Data
           , a -> Value b -> Value a
(a -> b) -> Value a -> Value b
(forall a b. (a -> b) -> Value a -> Value b)
-> (forall a b. a -> Value b -> Value a) -> Functor Value
forall a b. a -> Value b -> Value a
forall a b. (a -> b) -> Value a -> Value b
forall (f :: * -> *).
(forall a b. (a -> b) -> f a -> f b)
-> (forall a b. a -> f b -> f a) -> Functor f
<$ :: a -> Value b -> Value a
$c<$ :: forall a b. a -> Value b -> Value a
fmap :: (a -> b) -> Value a -> Value b
$cfmap :: forall a b. (a -> b) -> Value a -> Value b
Functor, Value a -> Bool
(a -> m) -> Value a -> m
(a -> b -> b) -> b -> Value a -> b
(forall m. Monoid m => Value m -> m)
-> (forall m a. Monoid m => (a -> m) -> Value a -> m)
-> (forall m a. Monoid m => (a -> m) -> Value a -> m)
-> (forall a b. (a -> b -> b) -> b -> Value a -> b)
-> (forall a b. (a -> b -> b) -> b -> Value a -> b)
-> (forall b a. (b -> a -> b) -> b -> Value a -> b)
-> (forall b a. (b -> a -> b) -> b -> Value a -> b)
-> (forall a. (a -> a -> a) -> Value a -> a)
-> (forall a. (a -> a -> a) -> Value a -> a)
-> (forall a. Value a -> [a])
-> (forall a. Value a -> Bool)
-> (forall a. Value a -> Int)
-> (forall a. Eq a => a -> Value a -> Bool)
-> (forall a. Ord a => Value a -> a)
-> (forall a. Ord a => Value a -> a)
-> (forall a. Num a => Value a -> a)
-> (forall a. Num a => Value a -> a)
-> Foldable Value
forall a. Eq a => a -> Value a -> Bool
forall a. Num a => Value a -> a
forall a. Ord a => Value a -> a
forall m. Monoid m => Value m -> m
forall a. Value a -> Bool
forall a. Value a -> Int
forall a. Value a -> [a]
forall a. (a -> a -> a) -> Value a -> a
forall m a. Monoid m => (a -> m) -> Value a -> m
forall b a. (b -> a -> b) -> b -> Value a -> b
forall a b. (a -> b -> b) -> b -> Value a -> b
forall (t :: * -> *).
(forall m. Monoid m => t m -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall m a. Monoid m => (a -> m) -> t a -> m)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall a b. (a -> b -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall b a. (b -> a -> b) -> b -> t a -> b)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. (a -> a -> a) -> t a -> a)
-> (forall a. t a -> [a])
-> (forall a. t a -> Bool)
-> (forall a. t a -> Int)
-> (forall a. Eq a => a -> t a -> Bool)
-> (forall a. Ord a => t a -> a)
-> (forall a. Ord a => t a -> a)
-> (forall a. Num a => t a -> a)
-> (forall a. Num a => t a -> a)
-> Foldable t
product :: Value a -> a
$cproduct :: forall a. Num a => Value a -> a
sum :: Value a -> a
$csum :: forall a. Num a => Value a -> a
minimum :: Value a -> a
$cminimum :: forall a. Ord a => Value a -> a
maximum :: Value a -> a
$cmaximum :: forall a. Ord a => Value a -> a
elem :: a -> Value a -> Bool
$celem :: forall a. Eq a => a -> Value a -> Bool
length :: Value a -> Int
$clength :: forall a. Value a -> Int
null :: Value a -> Bool
$cnull :: forall a. Value a -> Bool
toList :: Value a -> [a]
$ctoList :: forall a. Value a -> [a]
foldl1 :: (a -> a -> a) -> Value a -> a
$cfoldl1 :: forall a. (a -> a -> a) -> Value a -> a
foldr1 :: (a -> a -> a) -> Value a -> a
$cfoldr1 :: forall a. (a -> a -> a) -> Value a -> a
foldl' :: (b -> a -> b) -> b -> Value a -> b
$cfoldl' :: forall b a. (b -> a -> b) -> b -> Value a -> b
foldl :: (b -> a -> b) -> b -> Value a -> b
$cfoldl :: forall b a. (b -> a -> b) -> b -> Value a -> b
foldr' :: (a -> b -> b) -> b -> Value a -> b
$cfoldr' :: forall a b. (a -> b -> b) -> b -> Value a -> b
foldr :: (a -> b -> b) -> b -> Value a -> b
$cfoldr :: forall a b. (a -> b -> b) -> b -> Value a -> b
foldMap' :: (a -> m) -> Value a -> m
$cfoldMap' :: forall m a. Monoid m => (a -> m) -> Value a -> m
foldMap :: (a -> m) -> Value a -> m
$cfoldMap :: forall m a. Monoid m => (a -> m) -> Value a -> m
fold :: Value m -> m
$cfold :: forall m. Monoid m => Value m -> m
Foldable, Functor Value
Foldable Value
Functor Value
-> Foldable Value
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> Value a -> f (Value b))
-> (forall (f :: * -> *) a.
    Applicative f =>
    Value (f a) -> f (Value a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> Value a -> m (Value b))
-> (forall (m :: * -> *) a. Monad m => Value (m a) -> m (Value a))
-> Traversable Value
(a -> f b) -> Value a -> f (Value b)
forall (t :: * -> *).
Functor t
-> Foldable t
-> (forall (f :: * -> *) a b.
    Applicative f =>
    (a -> f b) -> t a -> f (t b))
-> (forall (f :: * -> *) a. Applicative f => t (f a) -> f (t a))
-> (forall (m :: * -> *) a b.
    Monad m =>
    (a -> m b) -> t a -> m (t b))
-> (forall (m :: * -> *) a. Monad m => t (m a) -> m (t a))
-> Traversable t
forall (m :: * -> *) a. Monad m => Value (m a) -> m (Value a)
forall (f :: * -> *) a. Applicative f => Value (f a) -> f (Value a)
forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Value a -> m (Value b)
forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Value a -> f (Value b)
sequence :: Value (m a) -> m (Value a)
$csequence :: forall (m :: * -> *) a. Monad m => Value (m a) -> m (Value a)
mapM :: (a -> m b) -> Value a -> m (Value b)
$cmapM :: forall (m :: * -> *) a b.
Monad m =>
(a -> m b) -> Value a -> m (Value b)
sequenceA :: Value (f a) -> f (Value a)
$csequenceA :: forall (f :: * -> *) a. Applicative f => Value (f a) -> f (Value a)
traverse :: (a -> f b) -> Value a -> f (Value b)
$ctraverse :: forall (f :: * -> *) a b.
Applicative f =>
(a -> f b) -> Value a -> f (Value b)
$cp2Traversable :: Foldable Value
$cp1Traversable :: Functor Value
Traversable
           , (forall x. Value a -> Rep (Value a) x)
-> (forall x. Rep (Value a) x -> Value a) -> Generic (Value a)
forall x. Rep (Value a) x -> Value a
forall x. Value a -> Rep (Value a) x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (Value a) x -> Value a
forall a x. Value a -> Rep (Value a) x
$cto :: forall a x. Rep (Value a) x -> Value a
$cfrom :: forall a x. Value a -> Rep (Value a) x
Generic, (forall a. Value a -> Rep1 Value a)
-> (forall a. Rep1 Value a -> Value a) -> Generic1 Value
forall a. Rep1 Value a -> Value a
forall a. Value a -> Rep1 Value a
forall k (f :: k -> *).
(forall (a :: k). f a -> Rep1 f a)
-> (forall (a :: k). Rep1 f a -> f a) -> Generic1 f
$cto1 :: forall a. Rep1 Value a -> Value a
$cfrom1 :: forall a. Value a -> Rep1 Value a
Generic1
           )

-- | Returns the annotation for a value.
valueAnn :: Value a -> a
valueAnn :: Value a -> a
valueAnn Value a
v =
  case Value a
v of
    Sections a
a [Section a]
_ -> a
a
    Number   a
a Number
_ -> a
a
    Text     a
a Text
_ -> a
a
    Atom     a
a Atom
_ -> a
a
    List     a
a [Value a]
_ -> a
a