optparse-enum-1.0.0.0: An enum-text based toolkit for optparse-applicative

Safe HaskellNone
LanguageHaskell2010

Text.Enum.Optparse

Contents

Synopsis

A simple Whole Example

A simple but complete example:

{-# LANGUAGE DeriveAnyClass    #-}
{-# LANGUAGE DerivingVia       #-}
{-# LANGUAGE OverloadedStrings #-}

import Fmt
import Text.Enum.Optparse
import Paths_optparse_enum

data Choice
  = C_version
  | C_hello
  deriving (Bounded,Enum,EnumText,Eq,Ord,Show)
  deriving (Buildable,TextParsable) via UsingEnumText Choice

parserDetails ::   ParserDetails
parserDetails =
  ParserDetails
    { _pd_desc   = "optparse-enum example program"
    , _pd_header = "A simple optparse-enum illustrative program"
    , _pd_footer = "See the optparse-enum page on Hackage for details"
    }

main :: IO ()
main = do
  choice <- parseIO parserDetails enumSwitchesP
  case choice of
    C_version -> print    version
    C_hello   -> putStrLn "Hello!"

The Drivers

parseIO :: ParserDetails -> Parser a -> IO a Source #

making an IO parser

parseIOWithArgs :: ParserDetails -> Parser a -> [String] -> IO a Source #

making an IO parser, specifying the arguments

pureParse :: ParserDetails -> Parser a -> [String] -> Maybe a Source #

making a functional parser

testCLI :: Show a => ParserDetails -> Parser a -> [String] -> IO () Source #

a testing helper

mkParserInfo

mkParserInfo :: ParserDetails -> Parser a -> ParserInfo a Source #

given a Parser makes up a corresponding ParserInfo

The Parser Generators

type MetaVar Source #

Arguments

 = String

name of a meta variable to be used in the docs

type HelpText Source #

Arguments

 = String

help text

type FlagName Source #

Arguments

 = String

name of a flag (will be forced to lower case)

type FlagChar Source #

Arguments

 = Char

charcter used for a short flag

enumArgP :: forall a. EnumText a => MetaVar -> Parser a Source #

parsing an EnumText argument

argP :: TextParsable a => MetaVar -> HelpText -> Parser a Source #

pasring a TextParsable argument

argP' :: (Text -> Either String a) -> MetaVar -> String -> Parser a Source #

pasring an TextParsable argument, the parser being passed explicitly

enumOptP :: forall a. EnumText a => FlagChar -> MetaVar -> Parser a Source #

parsing an EnumText option

enumSwitchesP :: EnumText a => Parser a Source #

generate mutually exclusive switches based on EnumText a

shortEnumSwitchesP :: forall a. EnumText a => (a -> Maybe FlagChar) -> Parser a Source #

generate mutually exclusive switches based on EnumText a, with some short swich options as specified by the argument function