module Data.Configurator.Types
    ( Value(..)
    , Directive(..)
    , ParseError(..)
    , Key
    , Path
    , Config
    , Interpolate (..)
    ) where

import Protolude

import Data.Scientific (Scientific)

-- | An error that occurred during the low-level parsing of a configuration file.
newtype ParseError = ParseError Text
  deriving (Int -> ParseError -> ShowS
[ParseError] -> ShowS
ParseError -> String
(Int -> ParseError -> ShowS)
-> (ParseError -> String)
-> ([ParseError] -> ShowS)
-> Show ParseError
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [ParseError] -> ShowS
$cshowList :: [ParseError] -> ShowS
show :: ParseError -> String
$cshow :: ParseError -> String
showsPrec :: Int -> ParseError -> ShowS
$cshowsPrec :: Int -> ParseError -> ShowS
Show)

instance Exception ParseError

-- | An evaluated configuation.
type Config = Map Key Value

-- | The left-hand side of a configuration binding.
type Key = Text

-- | A packed 'FilePath'.
type Path = Text

-- | A key-value binding.
--type Binding = (Key, Value)

-- | A directive in a configuration file.
data Directive = Import Path
               | Bind Key Value
               | Group Key [Directive]
               | DirectiveComment Directive
                 deriving (Directive -> Directive -> Bool
(Directive -> Directive -> Bool)
-> (Directive -> Directive -> Bool) -> Eq Directive
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Directive -> Directive -> Bool
$c/= :: Directive -> Directive -> Bool
== :: Directive -> Directive -> Bool
$c== :: Directive -> Directive -> Bool
Eq, Int -> Directive -> ShowS
[Directive] -> ShowS
Directive -> String
(Int -> Directive -> ShowS)
-> (Directive -> String)
-> ([Directive] -> ShowS)
-> Show Directive
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Directive] -> ShowS
$cshowList :: [Directive] -> ShowS
show :: Directive -> String
$cshow :: Directive -> String
showsPrec :: Int -> Directive -> ShowS
$cshowsPrec :: Int -> Directive -> ShowS
Show)

-- | A general right-hand side value of a configuration binding.
data Value = Bool Bool
           -- ^ A Boolean. Represented in a configuration file as @on@
           -- or @off@, @true@ or @false@ (case sensitive).
           | String Text
           -- ^ A Unicode string.  Represented in a configuration file
           -- as text surrounded by double quotes.
           --
           -- Escape sequences:
           --
           -- * @\\n@ - newline
           --
           -- * @\\r@ - carriage return
           --
           -- * @\\t@ - horizontal tab
           --
           -- * @\\\\@ - backslash
           --
           -- * @\\\"@ - quotes
           --
           -- * @\\u@/xxxx/ - Unicode character, encoded as four
           --   hexadecimal digits
           --
           -- * @\\u@/xxxx/@\\u@/xxxx/ - Unicode character (as two
           --   UTF-16 surrogates)
           | Number Scientific
           -- ^ A number.
           | List [Value]
           -- ^ A heterogeneous list.  Represented in a configuration
           -- file as an opening square bracket \"@[@\", followed by a
           -- comma-separated series of values, ending with a closing
           -- square bracket \"@]@\".
             deriving (Value -> Value -> Bool
(Value -> Value -> Bool) -> (Value -> Value -> Bool) -> Eq Value
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Value -> Value -> Bool
$c/= :: Value -> Value -> Bool
== :: Value -> Value -> Bool
$c== :: Value -> Value -> Bool
Eq, Int -> Value -> ShowS
[Value] -> ShowS
Value -> String
(Int -> Value -> ShowS)
-> (Value -> String) -> ([Value] -> ShowS) -> Show Value
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Value] -> ShowS
$cshowList :: [Value] -> ShowS
show :: Value -> String
$cshow :: Value -> String
showsPrec :: Int -> Value -> ShowS
$cshowsPrec :: Int -> Value -> ShowS
Show)

-- | An interpolation directive.
data Interpolate = Literal Text
                 | Interpolate Text
                   deriving (Interpolate -> Interpolate -> Bool
(Interpolate -> Interpolate -> Bool)
-> (Interpolate -> Interpolate -> Bool) -> Eq Interpolate
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Interpolate -> Interpolate -> Bool
$c/= :: Interpolate -> Interpolate -> Bool
== :: Interpolate -> Interpolate -> Bool
$c== :: Interpolate -> Interpolate -> Bool
Eq, Int -> Interpolate -> ShowS
[Interpolate] -> ShowS
Interpolate -> String
(Int -> Interpolate -> ShowS)
-> (Interpolate -> String)
-> ([Interpolate] -> ShowS)
-> Show Interpolate
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Interpolate] -> ShowS
$cshowList :: [Interpolate] -> ShowS
show :: Interpolate -> String
$cshow :: Interpolate -> String
showsPrec :: Int -> Interpolate -> ShowS
$cshowsPrec :: Int -> Interpolate -> ShowS
Show)