yaop-0.1.2.1: Yet another option parser

Portabilityportable
Stabilityexperimental
Maintainersmolanka.zhacka@gmail.com
Safe HaskellNone

System.Console.YAOP

Contents

Description

YAOP is a library for options parsings that uses base GetOpt as a backend.

 {-# LANGUAGE TemplateHaskell #-}

 import System
 import System.Environment
 import System.Console.YAOP

 import Data.List
 import Data.Maybe

 -- | Options that are not mapped to data
 withoutData = dummy =: option [] ["action"] NoA "Do some action" (\_ _ -> putStrLn "IO Action")

 -- | Options data structure. Should use record syntax, may have more than one constructor
 data Options = Options { optFileName :: FilePath
                        , optCount :: Int
                        , optStuff :: [Either Int String]
                        } deriving (Show)

 -- | Default options
 defOptions = Options {optFileName = "default.txt", optCount = 0, optStuff = []}

 -- | This triggers YAOP's accessors generator, e.g.
 -- @modM_optFileName :: Monad m => (FilePath -> m FilePath) -> Options -> m Options@
 $(deriveModM ''Options)

 -- | Here we define a list of options that are mapped to Options
 optDesc = do
   modM_optFileName =: option ['f'] ["filename"] (ReqA "FN")
                       "Set some filename"
                       (\arg x -> print arg >> return (fromMaybe "" arg))
   modM_optCount    =: option ['c'] ["count"] (OptA "N")
                       "Set some count"
                       (\arg x -> return $ fromMaybe 100 (read `fmap` arg))
   modM_optStuff    =: option ['s'] ["stuff"] NoA
                       "Push \"foo\" to a list"
                        (\arg x -> return (Right "foo" : x))

 bothDesc = withoutData >> optDesc

 main = do
   (opts,args) <- parseOptions bothDesc defOptions defaultParsingConf =<< getArgs
   print opts
   print args

Synopsis

TH selectors generator

deriveModM :: Name -> Q [Dec]Source

Generate functions with (a -> m a) -> rec -> rec type for all fields of the specified record.

Construtors

data ArgReq Source

Specifies if argument is required, optional or not necessary

Constructors

NoA 
OptA String 
ReqA String 

Instances

data Opt a Source

Instances

Show (Opt a) 
(Monoid [Opt a], Monad (OptM a)) => MonadWriter [Opt a] (OptM a) 

data OptM a r Source

Instances

Monad (OptM a) 
(Monoid [Opt a], Monad (OptM a)) => MonadWriter [Opt a] (OptM a) 

optionSource

Arguments

:: String

short option, e.g.: [a]

-> [String]

long option, e.g.: ["add"]

-> ArgReq

specify if argument is required

-> String

help message

-> (Maybe String -> a -> IO a)

a function that takes an argument and modifies selected field

-> OptM a () 

Smart option constructor

Combine

(=:)Source

Arguments

:: MonadWriter [Opt t] (OptM t) 
=> ((t -> IO t) -> a -> IO a)

selector

-> OptM t ()

options

-> OptM a () 

Apply selector to options combinator

Selectors

dummy :: Monad m => (() -> m a) -> b -> m bSource

Dummy selector, selects nothing. Useful for some --help options.

firstM :: Monad m => (t -> m t1) -> (t, t2) -> m (t1, t2)Source

Monadic action over the first element, useful as selector.

secondM :: Monad m => (t -> m t2) -> (t1, t) -> m (t1, t2)Source

Monadic action over the second element, useful as selector.

Runner

data ParsingConf Source

Constructors

ParsingConf 

Fields

pcUsageHeader :: String

Usage message header

pcHelpFlag :: Maybe String

Name of help message flag, default: "help"

pcHelpExtraInfo :: String

Extra help information

pcPermuteArgs :: Bool

True means GetOpt's Permute, False means RequireOrder

defaultParsingConf :: ParsingConfSource

Default option parsing configuration

parseOptionsSource

Arguments

:: OptM t ()

options for datatype t

-> t

initial environment

-> ParsingConf

parsing configuration

-> [String]

raw arguments

-> IO (t, [String]) 

Run parser, return configured options environment and arguments