config-value-0.5: Simple, layout-based value language similar to YAML or JSON

Safe HaskellSafe
LanguageHaskell2010

Config

Description

This module parses files using the syntax demonstrated below. The full grammar is available in the Happy source file.

-- Line comments until newline
layout:
  based:
    configuration:
      {} -- empty section

    sections:
     "glguy"

    {- Block comments
       {- nested comments -}
       "O'caml style {- strings in comments"
       so you can comment out otherwise valid
       portions of your config
    -}
    atoms      : yes

    decimal    : -1234
    hexadecimal: 0x1234
    octal      : 0o1234
    binary     : 0b1010

lists:
   * sections: in-lists
     next-section: still-in-list
   * [ "inline", "lists" ]
   * * "nestable"
     * "layout"
     * "lists"
   * 3

unicode : "standard Haskell format strings (1 ≤ 2)\x2228(2 ≤ 3)"

Synopsis

Documentation

data Section Source #

A single section of a Value

Constructors

Section 

Instances

Eq Section Source # 

Methods

(==) :: Section -> Section -> Bool #

(/=) :: Section -> Section -> Bool #

Data Section Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Section -> c Section #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Section #

toConstr :: Section -> Constr #

dataTypeOf :: Section -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Section) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Section) #

gmapT :: (forall b. Data b => b -> b) -> Section -> Section #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Section -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Section -> r #

gmapQ :: (forall d. Data d => d -> u) -> Section -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Section -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Section -> m Section #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Section -> m Section #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Section -> m Section #

Read Section Source # 
Show Section Source # 
Generic Section Source # 

Associated Types

type Rep Section :: * -> * #

Methods

from :: Section -> Rep Section x #

to :: Rep Section x -> Section #

type Rep Section Source # 
type Rep Section = D1 (MetaData "Section" "Config.Value" "config-value-0.5-1HCDOGaS28yElYuxvvBJsR" False) (C1 (MetaCons "Section" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "sectionName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)) (S1 (MetaSel (Just Symbol "sectionValue") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Value))))

data Value Source #

Sum type of the values supported by this language.

Constructors

Sections [Section] 
Number Int Integer

base number

Floating Integer Integer

coef exponent: coef * 10 ^ exponent

Text Text 
Atom Atom 
List [Value] 

Instances

Eq Value Source # 

Methods

(==) :: Value -> Value -> Bool #

(/=) :: Value -> Value -> Bool #

Data Value Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Value -> c Value #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Value #

toConstr :: Value -> Constr #

dataTypeOf :: Value -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Value) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Value) #

gmapT :: (forall b. Data b => b -> b) -> Value -> Value #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Value -> r #

gmapQ :: (forall d. Data d => d -> u) -> Value -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Value -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Value -> m Value #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Value -> m Value #

Read Value Source # 
Show Value Source # 

Methods

showsPrec :: Int -> Value -> ShowS #

show :: Value -> String #

showList :: [Value] -> ShowS #

Generic Value Source # 

Associated Types

type Rep Value :: * -> * #

Methods

from :: Value -> Rep Value x #

to :: Rep Value x -> Value #

type Rep Value Source # 

newtype Atom Source #

Wrapper to distinguish Atom from Text by type in a configuration.

Constructors

MkAtom 

Fields

Instances

Eq Atom Source # 

Methods

(==) :: Atom -> Atom -> Bool #

(/=) :: Atom -> Atom -> Bool #

Data Atom Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Atom -> c Atom #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Atom #

toConstr :: Atom -> Constr #

dataTypeOf :: Atom -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c Atom) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Atom) #

gmapT :: (forall b. Data b => b -> b) -> Atom -> Atom #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Atom -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Atom -> r #

gmapQ :: (forall d. Data d => d -> u) -> Atom -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Atom -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Atom -> m Atom #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Atom -> m Atom #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Atom -> m Atom #

Ord Atom Source # 

Methods

compare :: Atom -> Atom -> Ordering #

(<) :: Atom -> Atom -> Bool #

(<=) :: Atom -> Atom -> Bool #

(>) :: Atom -> Atom -> Bool #

(>=) :: Atom -> Atom -> Bool #

max :: Atom -> Atom -> Atom #

min :: Atom -> Atom -> Atom #

Read Atom Source # 
Show Atom Source # 

Methods

showsPrec :: Int -> Atom -> ShowS #

show :: Atom -> String #

showList :: [Atom] -> ShowS #

IsString Atom Source # 

Methods

fromString :: String -> Atom #

Generic Atom Source # 

Associated Types

type Rep Atom :: * -> * #

Methods

from :: Atom -> Rep Atom x #

to :: Rep Atom x -> Atom #

type Rep Atom Source # 
type Rep Atom = D1 (MetaData "Atom" "Config.Value" "config-value-0.5-1HCDOGaS28yElYuxvvBJsR" True) (C1 (MetaCons "MkAtom" PrefixI True) (S1 (MetaSel (Just Symbol "atomName") NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Text)))

parse Source #

Arguments

:: Text

Source

-> Either String Value

Either ErrorMessage Result

Parse a configuration file and return the result on the right, or the position of an error on the left. Note: Text file lines are terminated by new-lines.

pretty :: Value -> Doc Source #

Pretty-print a Value as shown in the example. Sections will nest complex values underneath with indentation and simple values will be rendered on the same line as their section.