getopt-generics: Simple command line argument parsing

[ bsd3, console, library, system ] [ Propose Tags ]

"getopt-generics" tries to make it very simple to create command line argument parsers. An introductory example can be found in the README.


[Skip to Readme]

Modules

[Index]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1, 0.1.1, 0.2, 0.3, 0.4, 0.4.1, 0.5, 0.6, 0.6.1, 0.6.2, 0.6.3, 0.7, 0.7.1, 0.7.1.1, 0.8, 0.9, 0.10, 0.10.0.1, 0.11, 0.11.0.1, 0.11.0.2, 0.11.0.3, 0.12, 0.13, 0.13.0.1, 0.13.0.2, 0.13.0.3, 0.13.0.4, 0.13.1.0
Dependencies base (>=4 && <5), base-compat (>=0.8), base-orphans, generics-sop, tagged [details]
License BSD-3-Clause
Copyright Zalora South East Asia Pte Ltd
Author Linh Nguyen, Sönke Hahn
Maintainer linh.nguyen@zalora.com, soenke.hahn@zalora.com
Category Console, System
Home page https://github.com/zalora/getopt-generics#readme
Bug tracker https://github.com/zalora/getopt-generics/issues
Source repo head: git clone https://github.com/zalora/getopt-generics
Uploaded by SoenkeHahn at 2015-07-16T06:27:20Z
Distributions Arch:0.13.1.0, Debian:0.13.0.4, LTSHaskell:0.13.1.0, NixOS:0.13.1.0, Stackage:0.13.1.0
Reverse Dependencies 1 direct, 0 indirect [details]
Downloads 22787 total (100 in the last 30 days)
Rating (no votes yet) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2015-07-16 [all 1 reports]

Readme for getopt-generics-0.8

[back to package description]

getopt-generics

Status

This library is experimental.

Usage

getopt-generics tries to make it very simple to create executables that parse command line options. All you have to do is to define a type and derive some instances:

{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE DeriveGeneric #-}

module Readme where

import Data.Typeable
import GHC.Generics
import System.Console.GetOpt.Generics
import System.Environment

data Options
  = Options {
    port :: Int,
    daemonize :: Bool,
    config :: Maybe FilePath
  }
  deriving (Show, GHC.Generics.Generic)

instance System.Console.GetOpt.Generics.Generic Options
instance HasDatatypeInfo Options

Then you can use getArguments to create a command-line argument parser:

main :: IO ()
main = do
  options <- getArguments
  print (options :: Options)

This program has

  • a non-optional --port flag with an integer argument,
  • a boolean flag --daemonize,
  • an optional flag --config expecting a file argument and
  • a generic --help option.

Here's in example of the program above in bash:

$ program --port 8080 --config some/path
Options {port = 8080, daemonize = False, config = Just "some/path"}
$ program  --port 8080 --daemonize
Options {port = 8080, daemonize = True, config = Nothing}
$ program --port foo
not an integer: foo
$ program
missing option: --port=int
$ program --help
program
    --port=integer
    --daemonize
    --config=string (optional)

Constraints

There are some constraints that the defined datatype has to fulfill:

  • It has to have only one constructor,
  • that constructor has to have field selectors (i.e. use record syntax) and
  • all fields have to be of a type that has an instance for Option.

(Types declared with newtype are allowed with the same constraints.)

Using Custom Field Types

It is possible to use custom field types by providing an instance for Option. Here's an example:

data File = File FilePath
  deriving (Show, Typeable)

instance Option File where
  argumentType Proxy = "file"
  parseArgument f = Just (File f)

data FileOptions
  = FileOptions {
    file :: File
  }
  deriving (Show, GHC.Generics.Generic)

instance System.Console.GetOpt.Generics.Generic FileOptions
instance HasDatatypeInfo FileOptions

-- Returns: FileOptions {file = File "some/file"}
getFileOptions :: IO FileOptions
getFileOptions = withArgs (words "--file some/file") getArguments