-- | A library for setting up a commandline parser and help generator for an
-- application. It aims for conciseness, flexibility and composability. It
-- supports both non-modal and modal (with subcommands -- like darcs, cabal and
-- the like) applications.
--
-- The library supports two main styles of representing flags and
-- commands. These are called "Record" and "ADT", respectively, by the
-- library. The Record representation is more straightforward and easier to use
-- in most instances. The ADT interface is suitable for applications that
-- require exact correspondence between the commandline and its runtime
-- representation, or when an existing application is being ported to cmdlib
-- that is using this style to represent flags.
--
-- Using the Record-based interface, a simple Hello World application could
-- look like this:
--
-- > {-# LANGUAGE FlexibleInstances, MultiParamTypeClasses, DeriveDataTypeable #-}
-- > import System.Console.CmdLib
-- > import Control.Monad
-- >
-- > data Main = Main { greeting :: String, again :: Bool }
-- >     deriving (Typeable, Data, Eq)
-- >
-- > instance Attributes Main where
-- >     attributes _ = group "Options" [
-- >         greeting %> [ Help "The text of the greeting.", ArgHelp "TEXT"
-- >                     , Default "Hello world!" ],
-- >         again    %> Help "Say hello twice." ]
-- >
-- > instance RecordCommand Main where
-- >     mode_summary _ = "Hello world with argument parsing."
-- >
-- > main = getArgs >>= executeR Main {} >>= \opts -> do
-- >   putStrLn (greeting opts)
--
-- Then, saying ./hello --help will give us:
--
-- > Hello world with argument parsing.
-- >
-- > Options:
-- >     --greeting=TEXT   The text of the greeting. (default: Hello world!)
-- >     --again[=yes|no]  Say hello twice. (default: no)

module System.Console.CmdLib (
  -- * News
  --
  -- | Since version 0.3: "dispatchR" no longer takes a cmd argument, as it was
  -- never used for anything and was simply confusing. A new function,
  -- "dispatchOr" has been added to allow the program to continue despite
  -- otherwise fatal errors (unknown command, unknown flags).  New function,
  -- "commandNames", has been added, to go from [CommandWrap] to [String]. The
  -- "CommandWrap" type is now exported (opaque).  The "RecordCommand" class
  -- now has a mode_help method. "RecordMode" is no longer exported.
  --
  -- | Since version 0.2: The Positional arguments are no longer required to be
  -- strings. A default (fallback) command may be provided to
  -- "dispatch"/"dispatchR" (this has also incompatibly changed their
  -- signature, sorry about that! I have tried to make this extensible
  -- though...). The "help" command can now be disabled (dispatch [noHelp]
  -- ...). Commands can now specify how to process options: permuted,
  -- non-permuted or no options at all. See "optionStyle".

  -- * Attributes
  --
  -- | To each flag, a number of attributes can be attached. Many reasonable
  -- defaults are provided by the library. The attributes are described by the
  -- "Attribute" type and are attached to flags using @"%>"@ and the related
  -- operators (all described in this section).

  Attribute(..), enable, disable, long, short, simple
  , (%%), (%>), (<%), (%+), (+%), everywhere, group

  -- * Flags

  -- | Flags (commandline options) can be represented in two basic styles,
  -- either as a plain ADT (algebraic data type) or as a record type. These two
  -- styles are implemented using the "ADT" wrapper for the former and and a
  -- "Record" wrapper for the latter. You need to make your type an instance of
  -- the "Attributes" class, which can be used to attach attributes to the
  -- flags.

  , ADT, Record, Attributes(..)

  -- * Commands
  , (%:), commandGroup, Command(..), dispatch, dispatchOr, execute, helpCommands, helpOptions
  , noHelp, defaultCommand, OptionStyle(..)
  , CommandWrap -- just the type (for signatures in users code)
  , commandNames

  -- * Record-based commands
  , RecordCommand(..), recordCommands, dispatchR, executeR

  -- * Utilities
  , globalFlag, readCommon, (<+<), HelpCommand(..), die

  -- * Convenience re-exports
  , Data, Typeable, getArgs
) where

import System.Console.CmdLib.Attribute
import System.Console.CmdLib.Flag
import System.Console.CmdLib.Command
import System.Console.CmdLib.ADTs
import System.Console.CmdLib.Record

import Data.Data
import Data.Typeable

import Data.IORef
import System.IO.Unsafe
import System.Environment

-- | Create a global setter/getter pair for a flag. The setter can be then
-- passed to the "Global" attribute and the getter used globally to query value
-- of that flag. Example:
--
-- > data Flag = Wibblify Int | Verbose Bool
-- > (setVerbose, isVerbose) = globalFlag False
-- >
-- > instance Attributes Flag where
-- >     attributes _ = Verbose %> Global setVerbose
-- >
-- > putVerbose str = isVerbose >>= flip when (putStrLn str)
globalFlag :: Typeable a => a -> (a -> IO (), IO a)
globalFlag def = unsafePerformIO $ do ref <- newIORef def
                                      return (writeIORef ref, readIORef ref)
{-# NOINLINE globalFlag #-}