config-schema-1.1.0.0: Schema definitions for the config-value package

Copyright(c) Eric Mertens 2017
LicenseISC
Maintaineremertens@gmail.com
Safe HaskellNone
LanguageHaskell2010

Config.Schema.Spec

Contents

Description

This module provides a set of types and operations for defining configuration file schemas.

These specifications are can be consumed by Config.Schema.Load and Config.Schema.Docs.

This is the schema system used by the glirc IRC client https://hackage.haskell.org/package/glirc. For a significant example, visit the Client.Configuration and Client.Configuration.Colors modules.

Synopsis

Specifying values

ValueSpec allows you to define specifications that will match parsed config-value configuration files. ValueSpec allows us to define the shape of configuration values that will match the specification as well as a way to process those matches.

Below we have an example configuration record that can be matched from a configuration file.

More documentation for defining key-value pairs is available below.

This configuration file expects either a given username or allows the user to ask for a random username. The (<!>) operator allows us to combine two alternatives as seen below. The config-value language distinguishes between atoms like random and strings like "random" allowing unambiguous special cases to be added in addition to free-form text.

{-# Language RecordWildCards, OverloadedStrings, ApplicativeDo #-}
module Example where

import Config.Schema
import Data.Functor.Alt ((<!>))
import Data.Maybe       (fromMaybe)
import Data.Text        (Text)

data Config = Config
  { userName :: UserName
  , retries  :: Int
  }

data UserName = Random | Given Text

userNameSpec :: ValueSpec UserName
userNameSpec = Random <$  atomSpec "random"
           <!> Given  <$> anySpec -- matches string literals

nameExample :: ValueSpec Config
nameExample = sectionsSpec "config" $

  do userName <- reqSection' "username" userNameSpec "Configured user name"

     retries  <- fromMaybe 3
             <$> optSection "retries" "Number of attempts (default: 3)"

     pure Config{..}

Examples:

username: random
retries: 5
-- Generates: Config { userName = Random, retries = 5 }

We can omit the retries:

username: random
-- Generates: Config { userName = Random, retries = 3 }

We can specify a specific username as a string literal instead of using the atom random:

username: "me"
-- Generates: Config { userName = Given "me", retries = 3 }

Sections can be reordered:

retries: 5
username: random
-- Generates: Config { userName = Random, retries = 5 }

data ValueSpec a Source #

Non-empty disjunction of value specifications. This type is the primary way to specify expected values.

Multiple specifications can be combined using this type's Alt instance.

To create ValueSpec values see Config.Schema.Spec

Instances
Functor ValueSpec Source # 
Instance details

Defined in Config.Schema.Types

Methods

fmap :: (a -> b) -> ValueSpec a -> ValueSpec b #

(<$) :: a -> ValueSpec b -> ValueSpec a #

Alt ValueSpec Source #

Left-biased choice between two specifications

Instance details

Defined in Config.Schema.Types

sectionsSpec Source #

Arguments

:: Text

unique documentation identifier

-> SectionsSpec a

underlying specification

-> ValueSpec a 

Named subsection value specification. The unique identifier will be used for generating a documentation section for this specification and should be unique within the scope of the specification being built.

assocSpec Source #

Arguments

:: ValueSpec a

underlying specification

-> ValueSpec [(Text, a)] 

Specification for a section list where the keys are user-defined. Values are matched against the underlying specification and returned as a list of section-name/value pairs.

Since: 0.3.0.0

atomSpec :: Text -> ValueSpec () Source #

Specification for matching a particular atom.

anyAtomSpec :: ValueSpec Text Source #

Specification for matching any atom. Matched atom is returned.

listSpec :: ValueSpec a -> ValueSpec [a] Source #

Specification for matching a list of values each satisfying a given element specification.

customSpec :: Text -> ValueSpec a -> (a -> Either Text b) -> ValueSpec b Source #

The custom specification allows an arbitrary function to be used to validate the value extracted by a specification. If Nothing is returned the value is considered to have failed validation.

namedSpec Source #

Arguments

:: Text

name

-> ValueSpec a

underlying specification

-> ValueSpec a 

Named value specification. This is useful for factoring complicated value specifications out in the documentation to avoid repetition of complex specifications.

class HasSpec a where Source #

Class of value specifications that don't require arguments.

Instances
HasSpec Int Source # 
Instance details

Defined in Config.Schema.Spec

HasSpec Int8 Source # 
Instance details

Defined in Config.Schema.Spec

HasSpec Int16 Source # 
Instance details

Defined in Config.Schema.Spec

HasSpec Int32 Source # 
Instance details

Defined in Config.Schema.Spec

HasSpec Int64 Source # 
Instance details

Defined in Config.Schema.Spec

HasSpec Integer Source # 
Instance details

Defined in Config.Schema.Spec

HasSpec Rational Source # 
Instance details

Defined in Config.Schema.Spec

HasSpec Word Source # 
Instance details

Defined in Config.Schema.Spec

HasSpec Word8 Source # 
Instance details

Defined in Config.Schema.Spec

HasSpec Word16 Source # 
Instance details

Defined in Config.Schema.Spec

HasSpec Word32 Source # 
Instance details

Defined in Config.Schema.Spec

HasSpec Word64 Source # 
Instance details

Defined in Config.Schema.Spec

HasSpec Text Source # 
Instance details

Defined in Config.Schema.Spec

HasSpec a => HasSpec [a] Source # 
Instance details

Defined in Config.Schema.Spec

Methods

anySpec :: ValueSpec [a] Source #

(HasSpec a, HasSpec b) => HasSpec (Either a b) Source # 
Instance details

Defined in Config.Schema.Spec

Methods

anySpec :: ValueSpec (Either a b) Source #

Specifying sections

Sections specifications allow you to define an unordered collection of required and optional sections using a convenient Applicative do-notation syntax.

Let's consider an example of a way to specify a name given a base and optional suffix.

{-# Language OverloadedStrings, ApplicativeDo #-}
module Example where

import Config.Schema
import Data.Text (Text)

nameExample :: ValueSpec Text
nameExample =
  sectionsSpec "name" $
  do x <- reqSection "base" "Base name"
     y <- optSection "suffix" "Optional name suffix"
     pure (maybe x (x <>) y)

Example configuration components and their extracted values.

base:     "VAR"
optional: "1"
-- Generates: VAR1

Order doesn't matter

optional: "1"
base:     "VAR"
-- Generates: VAR1

Optional fields can be omitted

base:     "VAR"
-- Generates: VAR

Unexpected sections will generate errors to help detect typos

base:     "VAR"
extra:    0
-- Failure due to unexpected extra section

All required sections must appear for successful match

optional: "1"
-- Failure due to missing required section

data SectionsSpec a Source #

A list of section specifications used to process a whole group of key-value pairs. Multiple section specifications can be combined using this type's Applicative instance.

To create SectionsSpec values see Config.Schema.Spec

Instances
Functor SectionsSpec Source # 
Instance details

Defined in Config.Schema.Types

Methods

fmap :: (a -> b) -> SectionsSpec a -> SectionsSpec b #

(<$) :: a -> SectionsSpec b -> SectionsSpec a #

Applicative SectionsSpec Source # 
Instance details

Defined in Config.Schema.Types

reqSection Source #

Arguments

:: HasSpec a 
=> Text

section name

-> Text

description

-> SectionsSpec a 

Specification for a required section with an implicit value specification.

optSection Source #

Arguments

:: HasSpec a 
=> Text

section name

-> Text

description

-> SectionsSpec (Maybe a) 

Specification for an optional section with an implicit value specification.

reqSection' Source #

Arguments

:: Text

section name

-> ValueSpec a

value specification

-> Text

description

-> SectionsSpec a 

Specification for a required section with an explicit value specification.

optSection' Source #

Arguments

:: Text

section name

-> ValueSpec a

value specification

-> Text

description

-> SectionsSpec (Maybe a) 

Specification for an optional section with an explicit value specification.

Derived specifications

oneOrList :: ValueSpec a -> ValueSpec [a] Source #

Specification that matches either a single element or multiple elements in a list. This can be convenient for allowing the user to avoid having to specify singleton lists in the configuration file.

yesOrNoSpec :: ValueSpec Bool Source #

Specification for using yes and no to represent booleans True and False respectively

stringSpec :: ValueSpec String Source #

Specification for matching any text as a String

numSpec :: Num a => ValueSpec a Source #

Specification for matching any integral number.

fractionalSpec :: Fractional a => ValueSpec a Source #

Specification for matching any fractional number.

Since: 0.2.0.0

nonemptySpec :: ValueSpec a -> ValueSpec (NonEmpty a) Source #

Matches a non-empty list.

Since: 0.2.0.0

oneOrNonemptySpec :: ValueSpec a -> ValueSpec (NonEmpty a) Source #

Matches a single element or a non-empty list.

Since: 0.2.0.0