turtle-1.2.3: Shell programming, Haskell-style

Safe HaskellNone

Turtle.Options

Contents

Description

Example usage of this module:

 -- options.hs

 {-# LANGUAGE OverloadedStrings #-}

 import Turtle

 parser :: Parser (Text, Int)
 parser = (,) <$> optText "name" 'n' "Your first name"
              <*> optInt  "age"  'a' "Your current age"

 main = do
     (name, age) <- options "Greeting script" parser
     echo (format ("Hello there, "%s) name)
     echo (format ("You are "%d%" years old") age)
 $ ./options --name John --age 42
 Hello there, John
 You are 42 years old
 $ ./options --help
 Greeting script

 Usage: options (-n|--name NAME) (-a|--age AGE)

 Available options:
  -h,--help                Show this help text
  --name NAME              Your first name
  --age AGE                Your current age

Synopsis

Types

data Parser a

A Parser a is an option parser returning a value of type a.

data ArgName Source

The name of a command-line argument

This is used to infer the long name and metavariable for the command line flag. For example, an ArgName of "name" will create a --name flag with a NAME metavariable

Instances

data CommandName Source

The name of a sub-command

This is lower-cased to create a sub-command. For example, a CommandName of "Name" will parse name on the command line before parsing the remaining arguments using the command's subparser.

type ShortName = CharSource

The short one-character abbreviation for a flag (i.e. -n)

data Description Source

A brief description of what your program does

This description will appear in the header of the --help output

data HelpMessage Source

A helpful message explaining what a flag does

This will appear in the --help output

Flag-based option parsers

switch :: ArgName -> ShortName -> Optional HelpMessage -> Parser BoolSource

This parser returns True if the given flag is set and False if the flag is absent

optText :: ArgName -> ShortName -> Optional HelpMessage -> Parser TextSource

Parse a Text value as a flag-based option

optInt :: ArgName -> ShortName -> Optional HelpMessage -> Parser IntSource

Parse an Int as a flag-based option

optInteger :: ArgName -> ShortName -> Optional HelpMessage -> Parser IntegerSource

Parse an Integer as a flag-based option

optDouble :: ArgName -> ShortName -> Optional HelpMessage -> Parser DoubleSource

Parse a Double as a flag-based option

optPath :: ArgName -> ShortName -> Optional HelpMessage -> Parser FilePathSource

Parse a FilePath value as a flag-based option

optRead :: Read a => ArgName -> ShortName -> Optional HelpMessage -> Parser aSource

Parse any type that implements Read

opt :: (Text -> Maybe a) -> ArgName -> ShortName -> Optional HelpMessage -> Parser aSource

Build a flag-based option parser for any type by providing a Text-parsing function

Positional argument parsers

argText :: ArgName -> Optional HelpMessage -> Parser TextSource

Parse a Text as a positional argument

argInt :: ArgName -> Optional HelpMessage -> Parser IntSource

Parse an Int as a positional argument

argInteger :: ArgName -> Optional HelpMessage -> Parser IntegerSource

Parse an Integer as a positional argument

argDouble :: ArgName -> Optional HelpMessage -> Parser DoubleSource

Parse a Double as a positional argument

argPath :: ArgName -> Optional HelpMessage -> Parser FilePathSource

Parse a FilePath as a positional argument

argRead :: Read a => ArgName -> Optional HelpMessage -> Parser aSource

Parse any type that implements Read as a positional argument

arg :: (Text -> Maybe a) -> ArgName -> Optional HelpMessage -> Parser aSource

Build a positional argument parser for any type by providing a Text-parsing function

Consume parsers

subcommand :: CommandName -> Description -> Parser a -> Parser aSource

Create a sub-command that parses CommandName and then parses the rest of the command-line arguments

The sub-command will have its own Description and help text

options :: MonadIO io => Description -> Parser a -> io aSource

Parse the given options from the command line