harg-0.3.0.0: Haskell program configuration using higher kinded data

Safe HaskellNone
LanguageHaskell2010

Options.Harg.Sources.Types

Synopsis

Documentation

data SourceRunResult a Source #

Holds errors that occur when running a source.

Constructors

OptNotFound

Source doesn't include the option

OptFoundNoParse OptError

Option cannot be parsed from source

OptParsed a

Successful parsing

Instances
Functor SourceRunResult Source # 
Instance details

Defined in Options.Harg.Sources.Types

Methods

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

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

class GetSource (c :: (Type -> Type) -> Type) (f :: Type -> Type) where Source #

This class enables a type that describes a source to fetch the source contents, potentially producing side effects (e.g. reading a file).

Associated Types

type SourceVal c :: Type Source #

The type that will be returned when the source is read.

Methods

getSource :: HargCtx -> c f -> IO (SourceVal c) Source #

Instances
GetSource NoSource f Source # 
Instance details

Defined in Options.Harg.Sources.NoSource

Associated Types

type SourceVal NoSource :: Type Source #

GetSource EnvSource f Source # 
Instance details

Defined in Options.Harg.Sources.Env

Associated Types

type SourceVal EnvSource :: Type Source #

GetSource DefaultStrSource f Source # 
Instance details

Defined in Options.Harg.Sources.DefaultStr

Associated Types

type SourceVal DefaultStrSource :: Type Source #

GetSource YAMLSource Identity Source # 
Instance details

Defined in Options.Harg.Sources.YAML

Associated Types

type SourceVal YAMLSource :: Type Source #

GetSource JSONSource Identity Source # 
Instance details

Defined in Options.Harg.Sources.JSON

Associated Types

type SourceVal JSONSource :: Type Source #

(GetSource l f, GetSource r f) => GetSource (l :* r) f Source # 
Instance details

Defined in Options.Harg.Sources.Types

Associated Types

type SourceVal (l :* r) :: Type Source #

Methods

getSource :: HargCtx -> (l :* r) f -> IO (SourceVal (l :* r)) Source #

class RunSource s a where Source #

This class is used to run the result of running getSource on the configuration options. In order for it to work, all types used in the source configuration need to have a GetSource instance, and their associated SourceVal types need to have a RunSource instance.

Methods

runSource :: Applicative f => s -> a (Compose Opt f) -> [a (Compose SourceRunResult f)] Source #

Instances
RunSource () a Source # 
Instance details

Defined in Options.Harg.Sources.Types

Methods

runSource :: Applicative f => () -> a (Compose Opt f) -> [a (Compose SourceRunResult f)] Source #

FunctorB a => RunSource EnvSourceVal a Source # 
Instance details

Defined in Options.Harg.Sources.Env

FunctorB a => RunSource DefaultStrSourceVal a Source # 
Instance details

Defined in Options.Harg.Sources.DefaultStr

(FromJSON (a Maybe), FunctorB a) => RunSource YAMLSourceVal a Source # 
Instance details

Defined in Options.Harg.Sources.YAML

(FromJSON (a Maybe), FunctorB a) => RunSource JSONSourceVal a Source # 
Instance details

Defined in Options.Harg.Sources.JSON

(RunSource l a, RunSource r a) => RunSource (l, r) a Source # 
Instance details

Defined in Options.Harg.Sources.Types

Methods

runSource :: Applicative f => (l, r) -> a (Compose Opt f) -> [a (Compose SourceRunResult f)] Source #

data ConfigFile Source #

This type describes configuration files, for use with e.g. the JSON source. The reason to not use FilePath directly is that the user might prefer to do nothing if the option for the config file has not been not provided, and there's no default. Because this type has an IsString instance, it's very easy to define an option. For example, to define a json source with a default value:

  srcOpt :: JSONSource Opt
  srcOpt = JSONSource jsonOpt
    where
      jsonOpt
        = optionWith strParser
            ( long "json-config"
            . defaultVal (ConfigFile "~/config.json")
            )

And an optional JSON source:

  srcOpt :: JSONSource Opt
  srcOpt = JSONSource jsonOpt
    where
      jsonOpt
        = optionWith strParser
            ( long "json-config"
            . defaultVal NoConfigFile
            )
Instances
IsString ConfigFile Source # 
Instance details

Defined in Options.Harg.Sources.Types