Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- data SourceRunResult a
- class GetSource (c :: (Type -> Type) -> Type) (f :: Type -> Type) where
- class RunSource s a where
- runSource :: Applicative f => s -> a (Compose Opt f) -> [a (Compose SourceRunResult f)]
- data ConfigFile
Documentation
data SourceRunResult a Source #
Holds errors that occur when running a source.
OptNotFound | Source doesn't include the option |
OptFoundNoParse OptError | Option cannot be parsed from source |
OptParsed a | Successful parsing |
Instances
Functor SourceRunResult Source # | |
Defined in Options.Harg.Sources.Types 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).
Instances
GetSource NoSource f Source # | |
GetSource EnvSource f Source # | |
GetSource DefaultStrSource f Source # | |
Defined in Options.Harg.Sources.DefaultStr type SourceVal DefaultStrSource :: Type Source # getSource :: HargCtx -> DefaultStrSource f -> IO (SourceVal DefaultStrSource) Source # | |
GetSource YAMLSource Identity Source # | |
Defined in Options.Harg.Sources.YAML type SourceVal YAMLSource :: Type Source # getSource :: HargCtx -> YAMLSource Identity -> IO (SourceVal YAMLSource) Source # | |
GetSource JSONSource Identity Source # | |
Defined in Options.Harg.Sources.JSON type SourceVal JSONSource :: Type Source # getSource :: HargCtx -> JSONSource Identity -> IO (SourceVal JSONSource) Source # | |
(GetSource l f, GetSource r f) => GetSource (l :* r) f 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.
runSource :: Applicative f => s -> a (Compose Opt f) -> [a (Compose SourceRunResult f)] Source #
Instances
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 # | |
Defined in Options.Harg.Sources.Types fromString :: String -> ConfigFile # |