{-# LANGUAGE Safe #-}
{-
Copyright (c) 2005-2011 John Goerzen <jgoerzen@complete.org>

All rights reserved.

For license and copyright information, see the file LICENSE
-}

{- |
   Module     : MissingH.getOpt
   Copyright  : Copyright (C) 2005-2011 John Goerzen
   SPDX-License-Identifier: BSD-3-Clause

   Stability  : stable
   Portability: portable

Written by John Goerzen, jgoerzen\@complete.org

Utilities for command-line parsing, including wrappers around
the standard System.Console.GetOpt module.
-}
module System.Console.GetOpt.Utils (parseCmdLine,
                        validateCmdLine,
                        StdOption,
                        stdRequired,
                        stdOptional
                       )
where
import safe System.Console.GetOpt
    ( getOpt, usageInfo, ArgOrder, OptDescr )
import safe System.Environment ( getArgs )

{- | Simple command line parser -- a basic wrapper around the system's
default getOpt.  See the System.Console.GetOpt manual for a description of the
first two parameters.

The third parameter is a usage information header.

The return value consists of the list of parsed flags and a list of
non-option arguments. -}
parseCmdLine :: ArgOrder a -> [OptDescr a] -> String -> IO ([a], [String])
parseCmdLine :: forall a.
ArgOrder a -> [OptDescr a] -> String -> IO ([a], [String])
parseCmdLine ArgOrder a
order [OptDescr a]
options String
header =
    do [String]
argv <- IO [String]
getArgs
       case ArgOrder a -> [OptDescr a] -> [String] -> ([a], [String], [String])
forall a.
ArgOrder a -> [OptDescr a] -> [String] -> ([a], [String], [String])
getOpt ArgOrder a
order [OptDescr a]
options [String]
argv of
         ([a]
o, [String]
n, []) -> ([a], [String]) -> IO ([a], [String])
forall (m :: * -> *) a. Monad m => a -> m a
return ([a]
o, [String]
n)
         ([a]
_, [String]
_, [String]
errors) -> IOError -> IO ([a], [String])
forall a. IOError -> IO a
ioError (String -> IOError
userError ([String] -> String
forall (t :: * -> *) a. Foldable t => t [a] -> [a]
concat [String]
errors String -> String -> String
forall a. [a] -> [a] -> [a]
++
                                               String -> [OptDescr a] -> String
forall a. String -> [OptDescr a] -> String
usageInfo String
header [OptDescr a]
options))

{- | Similar to 'parseCmdLine', but takes an additional function that validates
the post-parse command-line arguments.  This is useful, for example, in
situations where there are two arguments that are mutually-exclusive and only
one may legitimately be given at a time.

The return value of the function indicates whether or not it detected an
error condition.  If it returns Nothing, there is no error.  If it returns
Just String, there was an error, described by the String.
-}
validateCmdLine :: ArgOrder a -> [OptDescr a] -> String ->
                   (([a],[String]) -> Maybe String) -> IO ([a], [String])
validateCmdLine :: forall a.
ArgOrder a
-> [OptDescr a]
-> String
-> (([a], [String]) -> Maybe String)
-> IO ([a], [String])
validateCmdLine ArgOrder a
order [OptDescr a]
options String
header ([a], [String]) -> Maybe String
func =
    do ([a], [String])
res <- ArgOrder a -> [OptDescr a] -> String -> IO ([a], [String])
forall a.
ArgOrder a -> [OptDescr a] -> String -> IO ([a], [String])
parseCmdLine ArgOrder a
order [OptDescr a]
options String
header
       case ([a], [String]) -> Maybe String
func ([a], [String])
res of
         Maybe String
Nothing -> ([a], [String]) -> IO ([a], [String])
forall (m :: * -> *) a. Monad m => a -> m a
return ([a], [String])
res
         Just String
errormsg -> IOError -> IO ([a], [String])
forall a. IOError -> IO a
ioError (String -> IOError
userError (String
errormsg String -> String -> String
forall a. [a] -> [a] -> [a]
++ String
"\n" String -> String -> String
forall a. [a] -> [a] -> [a]
++
                                              String -> [OptDescr a] -> String
forall a. String -> [OptDescr a] -> String
usageInfo String
header [OptDescr a]
options))

{- | A type to standardize some common uses of GetOpt.

The first component of the tuple is the long name of the option.

The second component is empty if there is no arg, or has the arg otherwise. -}
type StdOption = (String, String)

{- | Handle a required argument. -}
stdRequired :: String           -- ^ Name of arg
            -> String -> StdOption
stdRequired :: String -> String -> StdOption
stdRequired String
name String
value = (String
name, String
value)

{- | Handle an optional argument. -}
stdOptional :: String           -- ^ Name of arg
               -> Maybe String -> StdOption
stdOptional :: String -> Maybe String -> StdOption
stdOptional String
name Maybe String
Nothing  = (String
name, String
"")
stdOptional String
name (Just String
x) = (String
name, String
x)