commander-cli: A command line argument/option parser library

[ cli, library, mit, options, parsing, program, system ] [ Propose Tags ]

A command line argument/option parser library.


[Skip to Readme]

Downloads

Maintainer's Corner

Package maintainers

For package maintainers and hackage trustees

Candidates

Versions [RSS] 0.1.0.0, 0.2.0.0, 0.2.0.1, 0.3.0.0, 0.4.0.0, 0.4.0.1, 0.4.1.1, 0.4.1.2, 0.5.0.0, 0.6.0.0, 0.6.1.0, 0.6.2.0, 0.7.0.0, 0.8.0.0, 0.9.0.0, 0.10.0.0, 0.10.0.1, 0.10.1.0, 0.10.1.1, 0.10.1.2, 0.10.1.3, 0.10.2.0, 0.11.0.0
Change log CHANGELOG.md
Dependencies base (>=4.12 && <5), bytestring (>=0.8 && <1), commander-cli, commandert (>=0.1), containers (>=0.1), directory (>=1.3 && <2), mtl (>=2.2 && <3), process (>=1.6 && <2), text (>=1.2 && <2), unordered-containers (>=0.2 && <1) [details]
License MIT
Copyright 2019 Samuel Schlesinger
Author Samuel Schlesinger
Maintainer sgschlesinger@gmail.com
Category System, CLI, Options, Parsing
Home page https://github.com/SamuelSchlesinger/commander-cli
Bug tracker https://github.com/SamuelSchlesinger/commander-cli/issues
Source repo head: git clone https://github.com/samuelschlesinger/commander-cli
Uploaded by sgschlesinger at 2020-10-08T17:46:54Z
Distributions NixOS:0.11.0.0
Executables task-manager
Downloads 4177 total (50 in the last 30 days)
Rating 2.0 (votes: 1) [estimated by Bayesian average]
Your Rating
  • λ
  • λ
  • λ
Status Docs available [build log]
Last success reported on 2020-10-08 [all 1 reports]

Readme for commander-cli-0.10.1.1

[back to package description]

Commander CLI

Hackage Build Status

This library is meant to allow Haskell programmers to quickly and easily construct command line interfaces with decent documentation.

One extension I use in these examples is -XTypeApplications. This extension allows us to use the @param syntax to apply an type-level argument explicitly to a function with a forall x ... in its type. This is as opposed to implicitly applying type-level arguments, as we do when we write fmap (+ 1) [1, 2, 3], applying the type [] to fmap. It's because of type inference in Haskell that we don't always have to apply our types explicitly, as many other languages force you to do using a syntax typically like fmap<[], Int> (+ 1) [1, 2, 3].`.

We can go to the command line and try out this example:

> :set -XTypeApplications
> :t fmap @[]
fmap @[] :: (a -> b) -> [a] -> [b]
> :t fmap @[] @Int
fmap @[] @Int :: (Int -> b) -> [Int] -> [b]
> :t fmap @[] @Int @Bool
fmap @[] @Int @Bool :: (Int -> Bool) -> [Int] -> [Bool]

The API of commander-cli allows for very profitable usage of type applications, because the description of our command line program will live at the type level.

Another extension we will use is -XDataKinds, which is only for the ability to use strings, or the kind Symbol, at the type level. Kinds are just the type of types, and so -XDataKinds allows us to have kinds which are actually data in their own right, like lists, strings, numbers, and custom Haskell data types. For us, we will use strings to represent the documentation of our program at the type level, as well as the names of options, flags, and arguments we want to parse. This allows us to generate documentation programs simply from the type signature of the CLI program we build.

Our first example will show a basic command line application, complete with help messages that display reasonable messages to the user.

main = command_
  . toplevel @"argument-taker"
  . arg @"example-argument" $ \arg ->
    raw $ do
      putStrLn arg

When you run this program with argument-taker help, you will see:

usage:
name: argument-taker
|
+- subprogram: help
|
`- argument: example-argument :: [Char]

The meaning of this documentation is that every path in the tree is a unique command. The one we've used is the help command. If we run this program with argument-taker hello we will see:

hello

Naturally, we might want to expand on the documentation of this program, as its not quite obvious enough what it does.

main = command_
  . toplevel @"argument-taker"
  . arg @"example-argument" $ \arg ->
    description @"Takes the argument and prints it"
  . raw $ do
      putStrLn arg

Printing out the documentation again with argument-taker help, we see:

usage:
name: argument-taker
|
+- subprogram: help
|
`- argument: example-argument :: [Char]
   |
   `- description: Takes the argument and prints it

Okay, so we can expand the documentation. But what if I have an option to pass to the same program? Well, we can pass an option like so:

main = command_
  . toplevel @"argument-taker"
  . optDef @"m" @"mode" "Print" $ \mode ->
    arg @"example-argument" $ \arg ->
    description @"Takes the argument and prints it or not, depending on the mode" 
  . raw $ do
      if mode == "Print" then putStrLn arg else pure ()

Now, when we run argument-taker help we will see:

usage:
name: argument-taker
|
+- subprogram: help
|
`- option: -m <mode :: [Char]>
   |
   `- argument: example-argument :: [Char]
      |
      `- description: Takes the argument and prints it or not, depending on the mode

Okay! So we can now create programs which take arguments and options, so what else do we want in a command line program? Flags! Lets add a flag to our example program:

main = command_
  . toplevel @"argument-taker"
  . optDef @"m" @"mode" "Print" $ \mode ->
    arg @"example-argument" $ \arg ->
    flag @"loud" $ \loud ->
    description @"Takes the argument and prints it or not, depending on the mode and possibly loudly" 
  . raw $ do
      let msg = if loud then map toUpper arg <> "!" else arg
      if mode == "Print" then putStrLn msg else pure ()

Running this with argument-taker help, we see:

usage:
name: argument-taker
|
+- subprogram: help
|
`- option: -m <mode :: [Char]>
   |
   `- argument: example-argument :: [Char]
      |
      `- flag: ~loud
         |
         `- description: Takes the argument and prints it or not, depending on the mode and possibly loudly

Okay, so we've added all of the normal command line things, but we haven't yet shown how to add a new command to our program, so lets do that. To do this, we can write:

main = command_
  . toplevel @"argument-taker"
  $ defaultProgram <+> sub @"shriek" (raw (putStrLn "AHHHHH!!"))
  where
  defaultProgram = 
      optDef @"m" @"mode" "Print" $ \mode ->
      arg @"example-argument" $ \arg ->
      flag @"loud" $ \loud ->
      description @"Takes the argument and prints it or not, depending on the mode and possibly loudly" 
    . raw $ do
        let msg = if loud then map toUpper arg <> "!" else arg
        if mode == "Print" then putStrLn msg else pure ()

Running this program with argument-taker help, we can see the docs yet again:

usage:
name: argument-taker
|
+- subprogram: help
|
+- option: -m <mode :: [Char]>
|  |
|  `- argument: example-argument :: [Char]
|     |
|     `- flag: ~loud
|        |
|        `- description: Takes the argument and prints it or not, depending on the mode and possibly loudly
|
`- subprogram: shriek

Awesome! So we have now shown how to use the primitives of CLI programs, as well as how to add new subprograms. One more thing I would like to show that is different from normal CLI libraries is that I added the ability to automatically search for environment variables and pass them to your program. I just liked this, as sometimes when I use a CLI program I forget this or that environment variable, and the documentation generation makes this self documenting in commander-cli. We can add this to our program by writing:

main = command_
  . toplevel @"argument-taker"
  $ env @"ARGUMENT_TAKER_DIRECTORY" \argumentTakerDirectory ->
      defaultProgram argumentTakerDirectory
  <+> sub @"shriek" (raw $ do
        setCurrentDirectory argumentTakerDirectory 
        putStrLn "AHHH!"
      )
  where
  defaultProgram argumentTakerDirectory = 
      optDef @"m" @"mode" "Print" $ \mode ->
      arg @"example-argument" $ \arg ->
      flag @"loud" $ \loud ->
      description @"Takes the argument and prints it or not, depending on the mode and possibly loudly" 
    . raw $ do
        setCurrentDirectory argumentTakerDirectory
        let msg = if loud then map toUpper arg <> "!" else arg
        if mode == "Print" then putStrLn msg else pure ()

Now, we will see argument-taker help as:

usage:
name: argument-taker
|
+- subprogram: help
|
`- required env: ARGUMENT_TAKER_DIRECTORY :: [Char]
   |
   +- option: -m <mode :: [Char]>
   |  |
   |  `- argument: example-argument :: [Char]
   |     |
   |     `- flag: ~loud
   |        |
   |        `- description: Takes the argument and prints it or not, depending on the mode and possibly loudly
   |
   `- subprogram: shriek

We can see that it documents the usage of this environment variable in a reasonable way, but its not clear where exactly what it does exactly. First, you might think to use the description combinator, but it isn't exactly made for describing an input, but for documenting a path of a program. We can fix this using the annotated combinator, which was made for describing inputs to our program:

main :: IO ()
main = command_
  . toplevel @"argument-taker"
  . annotated @"the directory we will go to for the program"
  $ env @"ARGUMENT_TAKER_DIRECTORY" \argumentTakerDirectory ->
      defaultProgram argumentTakerDirectory
  <+> sub @"shriek" (raw $ do
        setCurrentDirectory argumentTakerDirectory 
        putStrLn "AHHH!"
      )
  where
  defaultProgram argumentTakerDirectory = 
      optDef @"m" @"mode" "Print" $ \mode ->
      arg @"example-argument" $ \arg ->
      flag @"loud" $ \loud ->
      description @"Takes the argument and prints it or not, depending on the mode" 
    . raw $ do
        setCurrentDirectory argumentTakerDirectory
        let msg = if loud then map toUpper arg <> "!" else arg
        if mode == "Print" then putStrLn msg else pure ()

Running argument-taker help will result in:

usage:
name: argument-taker
|
+- subprogram: help
|
`- required env: ARGUMENT_TAKER_DIRECTORY :: [Char], the directory we will go to for the program
   |
   +- option: -m <mode :: [Char]>
   |  |
   |  `- argument: example-argument :: [Char]
   |     |
   |     `- flag: ~loud
   |        |
   |        `- description: Takes the argument and prints it or not, depending on the mode
   |
   `- subprogram: shriek

Design

The library is based around the following classes:

class Unrender r where
  unrender :: Text -> Maybe r

This class is what you will use to define the parsing of a type from text and can use any parsing library or whatever you want. Next, we have the class

class HasProgram p where
  data ProgramT p m a
  run :: ProgramT p IO a -> CommanderT State IO a
  hoist :: (forall x. m x -> n x) -> ProgramT p m a -> ProgramT p n a
  documentation :: Forest String

Instances of this class will define a syntactic element, a new instance of the data family ProgramT, as well as its semantics in terms of the CommanderT monad, which is something like a free backtracking monad. Users should not have to make instances of this class, as the common CLI elements are already defined as instances. Of course, you can if you want to, and it can be profitable to do so.