optparse-declarative: Declarative command line option parser

[ library, mit, system ] [ Propose Tags ]

Declarative and easy to use command line option parser


[Skip to Readme]

Modules

[Index]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1.0, 0.2.0, 0.3.0, 0.3.1, 0.4.0, 0.4.1, 0.4.2
Change log ChangeLog.md
Dependencies base (>=4.7 && <5), bytestring, fast-logger, monad-logger, mtl [details]
License MIT
Copyright (c) Hideyuki Tanaka 2015
Author Hideyuki Tanaka
Maintainer tanaka.hideyuki@gmail.com
Category System
Home page https://github.com/tanakh/optparse-declarative
Source repo head: git clone https://github.com/tanakh/optparse-declarative.git
Uploaded by HideyukiTanaka at 2015-06-23T16:04:21Z
Distributions
Downloads 2956 total (24 in the last 30 days)
Rating 2.25 (votes: 2) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2015-06-23 [all 1 reports]

Readme for optparse-declarative-0.2.0

[back to package description]

optparse-declarative

optparse-declarative is a declarative and easy to use command-line option parser.

Install

$ cabal install optparse-declarative

Usage

Writing a simple command

First, you need to enable DataKinds extension and import Options.Declarative module.

{-# LANGUAGE DataKinds #-}
import           Options.Declarative

Then, define the command line option as a type of the function. For example, this is a simple greeting program:

greet :: Flag "g" '["greet"] "STRING" "greeting message" (Def "Hello" String)
      -> Arg "NAME" String
      -> Cmd "greet"
greet msg name = Cmd $ do
    putStrLn $ get msg ++ ", " ++ get name ++ "!"

There are two type of options, Flag and Arg. Flag is named argument and Arg is unnamed argument. Last argument of both options is value type. If you need to specify default value, use the modifiers such as Def.

In above, variable msg has a very complex type (Flag "g" '["greet"] "STRING" "greeting message" (Def "Hello" String)). In order to get the value of usual type (in this case, that is String), you can use get function.

The whole type of command is Cmd. Cmd <description> is basically newtype of IO (), except this contains extra information.

When you define the command, there remains only invoking the command.

main :: IO ()
main = run_ greet

You can execute this program like this:

$ ghc simple.hs

$ ./simple
simple: not enough arguments
Try 'simple --help' for more information.

$ ./simple --help
Usage: simple [OPTION...] NAME
Options:
  -g STRING  --greet=STRING  greeting message
  -?         --help          display this help and exit

$ ./simple World
Hello, World!

$ ./simple --greet=Goodbye World
Goodbye, World!

Writing multiple sum-commands

You can write (nested) sub-commands.

Just groupe subcommands by Group, you got sub-command parser.

This is the example:

{-# LANGUAGE DataKinds #-}

import           Options.Declarative

main :: IO ()
main = run_ $
    Group "Test program for library"
    [ subCmd "greet"   greet
    , subCmd "connect" connect
    ]

greet :: Flag "g" '["greet"] "STRING" "greeting message" (Def "Hello" String)
      -> Flag "" '["decolate"] "" "decolate message" Bool
      -> Arg "NAME" String
      -> Cmd "Greeting command"
greet msg deco name = Cmd $ do
    let f x | get deco = "*** " ++ x ++ " ***"
            | otherwise = x
    putStrLn $ f $ get msg ++ ", " ++ get name ++ "!"

connect :: Flag "h" '["host"] "HOST" "host name"   (Def "localhost" String)
        -> Flag "p" '["port"] "PORT" "port number" (Def "8080"      Int   )
    -> Cmd "Connect command"
connect host port = Cmd $ do
    let addr = get host ++ ":" ++ show (get port)
    putStrLn $ "connect to " ++ addr

And this is the output:

$ ./subcmd --help
Usage: subcmd [OPTION...] <COMMAND> [ARGS...]
Options:
  -?  --help  display this help and exit

Commands:
  greet       Greeting command
  port        Server command

$ ./subcmd connect --port=1234
connect to localhost:1234

For more examples, please see example directory.