{-# LANGUAGE ConstraintKinds            #-}
{-# LANGUAGE CPP                        #-}
{-# LANGUAGE DataKinds                  #-}
{-# LANGUAGE DefaultSignatures          #-}
{-# LANGUAGE DeriveDataTypeable         #-}
{-# LANGUAGE DeriveGeneric              #-}
{-# LANGUAGE EmptyDataDecls             #-}
{-# LANGUAGE FlexibleInstances          #-}
{-# LANGUAGE FlexibleContexts           #-}
{-# LANGUAGE KindSignatures             #-}
{-# LANGUAGE MultiParamTypeClasses      #-}
{-# LANGUAGE RecordWildCards            #-}
{-# LANGUAGE ScopedTypeVariables        #-}
{-# LANGUAGE TypeFamilies               #-}
{-# LANGUAGE TypeOperators              #-}

-- | This library auto-generates command-line parsers for data types using
-- Haskell's built-in support for generic programming.  The best way to
-- understand how this library works is to walk through a few examples.
--
-- For example, suppose that you want to parse a record with named fields like
-- this:
--
-- > -- Example.hs
-- >
-- > {-# LANGUAGE DeriveGeneric     #-}
-- > {-# LANGUAGE OverloadedStrings #-}
-- > 
-- > import Options.Generic
-- > 
-- > data Example = Example { foo :: Int, bar :: Double }
-- >     deriving (Generic, Show)
-- > 
-- > instance ParseRecord Example
-- > 
-- > main = do
-- >     x <- getRecord "Test program"
-- >     print (x :: Example)
--
-- Named fields translate to flags which you can provide in any order:
--
-- > $ stack build optparse-generic
-- > $ stack runghc Example.hs -- --bar 2.5 --foo 1
-- > Example {foo = 1, bar = 2.5}
--
-- This also auto-generates @--help@ output:
--
-- > $ stack runghc Example.hs -- --help
-- > Test program
-- > 
-- > Usage: Example.hs --foo INT --bar DOUBLE
-- > 
-- > Available options:
-- >   -h,--help                Show this help text
--
-- You can also add help descriptions to each field, like this:
--
-- > {-# LANGUAGE DataKinds         #-}
-- > {-# LANGUAGE DeriveGeneric     #-}
-- > {-# LANGUAGE OverloadedStrings #-}
-- > {-# LANGUAGE TypeOperators     #-}
-- > 
-- > import Options.Generic
-- > 
-- > data Example = Example
-- >     { foo :: Int    <?> "Documentation for the foo flag"
-- >     , bar :: Double <?> "Documentation for the bar flag"
-- >     } deriving (Generic, Show)
-- > 
-- > instance ParseRecord Example
-- > 
-- > main = do
-- >     x <- getRecord "Test program"
-- >     print (x :: Example)
--
-- ... which produces the following @--help@ output:
--
-- > $ stack runghc Example.hs -- --help
-- > Test program
-- > 
-- > Usage: Example.hs --foo INT --bar DOUBLE
-- > 
-- > Available options:
-- >   -h,--help                Show this help text
-- >   --foo INT                Documentation for the foo flag
-- >   --bar DOUBLE             Documentation for the bar flag
--
-- However, any fields you document will be wrapped in the `Helpful`
-- constructor:
--
-- > $ stack runghc Example.hs -- --foo 1 --bar 2.5
-- > Example {foo = Helpful {unHelpful = 1}, bar = Helpful {unHelpful = 2.5}}
--
-- To avoid this, while still being able to document your fields, you may
-- generalize the definition of your record with a parameter 'w', and use
-- 'unwrapRecord'.
--
-- > {-# LANGUAGE DataKinds          #-}
-- > {-# LANGUAGE DeriveGeneric      #-}
-- > {-# LANGUAGE FlexibleInstances  #-}  -- One more extension.
-- > {-# LANGUAGE OverloadedStrings  #-}
-- > {-# LANGUAGE StandaloneDeriving #-}  -- To derive Show
-- > {-# LANGUAGE TypeOperators      #-}
-- >
-- > import Options.Generic
-- >
-- > data Example w = Example
-- >     { foo :: w ::: Int    <?> "Documentation for the foo flag"
-- >     , bar :: w ::: Double <?> "Documentation for the bar flag"
-- >     } deriving (Generic)
-- >
-- > instance ParseRecord (Example Wrapped)
-- > deriving instance Show (Example Unwrapped)
-- >
-- > main = do
-- >     x <- unwrapRecord "Test program"
-- >     print (x :: Example Unwrapped)
--
-- @Example Unwrapped@ is equivalent to a record type with simple fields:
--
-- > $ stack runghc Example.hs -- --foo 1 --bar 2.5
-- > Example {foo = 1, bar = 2.5}
--
-- You can also add default values to each `Read`able field, like this:
--
-- > {-# LANGUAGE DataKinds         #-}
-- > {-# LANGUAGE DeriveGeneric     #-}
-- > {-# LANGUAGE OverloadedStrings #-}
-- > {-# LANGUAGE TypeOperators     #-}
-- > 
-- > import Options.Generic
-- > 
-- > data Example = Example
-- >     { foo :: Int    <!> "1"
-- >     , bar :: String <!> "hello"
-- >     } deriving (Generic, Show)
-- > 
-- > instance ParseRecord Example
-- > 
-- > main = do
-- >     x <- getRecord "Test program"
-- >     print (x :: Example)
--
-- Default values will work alongside help descriptions and unwrapping.
--
-- For the following examples I encourage you to test what @--help@ output they
-- generate.
--
-- This library will also do the right thing if the fields have no labels:
--
-- > data Example = Example Int Double deriving (Generic, Show)
--
-- Fields without labels translate into positional command-line arguments:
--
-- > $ stack runghc Example.hs -- 1 2.5
-- > Example 1 2.5
--
-- Certain types of fields are given special treatment, such as in this
-- example:
--
-- > data Example = Example
-- >     { switch   :: Bool
-- >     , list     :: [Int]
-- >     , optional :: Maybe   Int
-- >     , first    :: First   Int
-- >     , last     :: Last    Int
-- >     , sum      :: Sum     Int
-- >     , product  :: Product Int
-- >     } deriving (Generic, Show)
--
-- This gives the following behavior:
--
-- > $ stack runghc Example.hs --
-- >       --switch
-- >       --optional 1
-- >       --list    1 --list    2
-- >       --first   1 --first   2
-- >       --last    1 --last    2
-- >       --sum     1 --sum     2
-- >       --product 1 --product 2
-- > Example {switch = True, list = [1,2], optional = Just 1, first = First 
-- > {getFirst = Just 1}, last = Last {getLast = Just 2}, sum = Sum {getSum =
-- > 3}, product = Product {getProduct = 2}}
-- > 
-- > $ stack runghc Example.hs
-- > Example {switch = False, list = [], optional = Nothing, first = First
-- > {getFirst = Nothing}, second = Last {getLast = Nothing}, sum = Sum {getSum
-- > = 0}, product = Product {getProduct = 1}}
--
-- If a datatype has multiple constructors:
--
-- > data Example
-- >     = Create { name :: Text, duration :: Maybe Int }
-- >     | Kill   { name :: Text }
-- >     deriving (Generic, Show)
--
-- ... then they will translate into subcommands named after each constructor:
--
-- > $ stack runghc Example.hs -- create --name foo --duration=60
-- > Create {name = "foo", duration = Just 60}
-- > $ stack runghc Example.hs -- kill --name foo
-- > Kill {name = "foo"}
--
-- This library also provides out-of-the-box support for many existing types,
-- like tuples and `Either`.
--
-- > {-# LANGUAGE DeriveGeneric     #-}
-- > {-# LANGUAGE OverloadedStrings #-}
-- > 
-- > import Options.Generic
-- > 
-- > main = do
-- >     x <- getRecord "Test program"
-- >     print (x :: Either Double Int)
--
-- > $ stack runghc Example.hs -- left 1.0
-- > Left 1.0
-- > $ stack runghc Example.hs -- right 2
-- > Right 2
-- 
-- > main = do
-- >     x <- getRecord "Test program"
-- >     print (x :: (Double, Int))
--
-- > $ stack runghc Example.hs -- 1.0 2
-- > (1.0,2)
--
-- ... and you can also just parse a single value:
--
-- > main = do
-- >     x <- getRecord "Test program"
-- >     print (x :: Int)
--
-- > $ stack runghc Example.hs -- 2
-- > 2
--
-- However, there are some types that this library cannot generate sensible
-- command-line parsers for, such as:
--
-- * recursive types:
--
--     > data Example = Example { foo :: Example }
--
-- * records whose fields are other records
--
--     > data Outer = Outer { foo :: Inner } deriving (Show, Generic)
--     > data Inner = Inner { bar :: Int   } deriving (Show, Generic)
--
-- * record fields  with nested `Maybe`s or nested lists
--
--     > data Example = Example { foo :: Maybe (Maybe Int) }
--     > data Example = Example { foo :: [[Int]]           }
--
-- If you try to auto-generate a parser for these types you will get an error at
-- compile time that will look something like this:
--
-- >     No instance for (ParseFields TheTypeOfYourField)
-- >       arising from a use of ‘Options.Generic.$gdmparseRecord’
-- >     In the expression: Options.Generic.$gdmparseRecord
-- >     In an equation for ‘parseRecord’:
-- >         parseRecord = Options.Generic.$gdmparseRecord
-- >     In the instance declaration for ‘ParseRecord TheTypeOfYourRecord’
--
-- You can customize the library's default behavior using the
-- `parseRecordWithModifiers` utility, like this:
--
-- > {-# LANGUAGE DeriveGeneric     #-}
-- > {-# LANGUAGE OverloadedStrings #-}
-- > 
-- > import Options.Generic
-- > 
-- > data Example = Example { foo :: Int, bar :: Double }
-- >     deriving (Generic, Show)
-- > 
-- > modifiers :: Modifiers
-- > modifiers = defaultModifiers
-- >     { shortNameModifier = firstLetter
-- >     }
-- >
-- > instance ParseRecord Example where
-- >     parseRecord = parseRecordWithModifiers modifiers
-- > 
-- > main = do
-- >     x <- getRecord "Test program"
-- >     print (x :: Example)

module Options.Generic (
    -- * Parsers
      getRecord
    , getRecordWith
    , getWithHelpWith
    , getWithHelp
    , getRecordPure
    , getRecordPureWith
    , unwrapRecord
    , unwrapWithHelp
    , unwrapRecordPure
    , unwrap
    , ParseRecord(..)
    , ParseFields(..)
    , ParseField(..)
    , Only(..)
    , getOnly
    , readIntegralBounded
    , Modifiers(..)
    , parseRecordWithModifiers
    , defaultModifiers
    , lispCaseModifiers
    , firstLetter
    , GenericParseRecord(..)

    -- * Help
    , type (<?>)(..)
    , type (<!>)(..)
    , type (<#>)(..)
    , type (:::)
    , Wrapped
    , Unwrapped
    , Unwrappable

    -- * Re-exports
    , Generic
    , Text
    , All(..)
    , Any(..)
    , First(..)
    , Last(..)
    , Sum(..)
    , Product(..)
    ) where

import Control.Applicative
import Control.Monad.IO.Class (MonadIO(..))
import Control.Monad.Trans.Except (runExcept)
import Control.Monad.Trans.Reader (runReaderT)
import Data.Char (isUpper, toLower, toUpper)
import Data.Data (Data)
import Data.Int (Int8, Int16, Int32, Int64)
import Data.Maybe (listToMaybe)
import Data.Monoid
import Data.List.NonEmpty (NonEmpty)
import Data.Proxy
import Data.Text (Text)
import Data.Time.Format.ISO8601 (ISO8601)
import Data.Tuple.Only (Only(..))
import Data.Typeable (Typeable)
import Data.Void (Void)
import Data.Word (Word8, Word16, Word32, Word64)
import GHC.Generics
import Prelude
import Options.Applicative (Parser, ReadM)

import Data.Time
    ( CalendarDiffDays
    , CalendarDiffTime
    , Day
    , LocalTime
    , TimeOfDay
    , TimeZone
    , UTCTime
    , ZonedTime
    )

import qualified Data.Text
import qualified Data.Text.Encoding
import qualified Data.Text.Lazy
import qualified Data.Text.Lazy.Encoding
import qualified Data.Time.Format.ISO8601     as ISO8601
import qualified Data.Typeable
import qualified Data.ByteString
import qualified Data.ByteString.Lazy
import qualified Options.Applicative          as Options
import qualified Options.Applicative.Types    as Options
import qualified Options.Applicative.NonEmpty as Options.NonEmpty
import qualified Text.Read

#if MIN_VERSION_base(4,7,0)
import GHC.TypeLits
#else
import Data.Singletons.TypeLits
#endif

#if MIN_VERSION_base(4,8,0)
import Numeric.Natural (Natural)
#endif

#if MIN_VERSION_filepath(1,4,100)
import System.OsPath
#endif

auto :: Read a => ReadM a
auto :: forall a. Read a => ReadM a
auto = do
    String
s <- ReadM String
Options.readerAsk
    case forall a. Read a => String -> Maybe a
Text.Read.readMaybe String
s of
        Just a
x  -> forall (m :: * -> *) a. Monad m => a -> m a
return a
x
        Maybe a
Nothing -> forall a. ParseError -> ReadM a
Options.readerAbort (Maybe String -> ParseError
Options.ShowHelpText forall a. Maybe a
Nothing)

{-| A class for all record fields that can be parsed from exactly one option or
    argument on the command line

    `parseField` has a default implementation for any type that implements
    `Read` and `Typeable`.  You can derive `Read` for many types and you can
    derive `Typeable` for any type if you enable the @DeriveDataTypeable@
    language extension
-}
class ParseField a where
    parseField
        :: Maybe Text
        -- ^ Help message
        -> Maybe Text
        -- ^ Field label
        -> Maybe Char
        -- ^ Short name
        -> Maybe String
        -- ^ Default value
        -> Parser a
    default parseField
        :: Maybe Text
        -- ^ Help message
        -> Maybe Text
        -- ^ Field label
        -> Maybe Char
        -- ^ Short name
        -> Maybe String
        -- ^ Default value
        -> Parser a
    parseField Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d = do
        let proxy :: Proxy a
proxy = forall {k} (t :: k). Proxy t
Proxy :: Proxy a
        case Maybe Text
m of
            Maybe Text
Nothing   -> do
                let fs :: Mod ArgumentFields a
fs =  forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.metavar (forall a (proxy :: * -> *). ParseField a => proxy a -> String
metavar Proxy a
proxy)
                       forall a. Semigroup a => a -> a -> a
<> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (forall (f :: * -> *) a. String -> Mod f a
Options.help forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
Data.Text.unpack) Maybe Text
h
                forall a. ReadM a -> Mod ArgumentFields a -> Parser a
Options.argument forall a. ParseField a => ReadM a
readField Mod ArgumentFields a
fs
            Just Text
name -> do
                let fs :: Mod OptionFields a
fs =  forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.metavar (forall a (proxy :: * -> *). ParseField a => proxy a -> String
metavar Proxy a
proxy)
                       forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.long (Text -> String
Data.Text.unpack Text
name)
                       forall a. Semigroup a => a -> a -> a
<> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (forall (f :: * -> *) a. String -> Mod f a
Options.help forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
Data.Text.unpack) Maybe Text
h
                       forall a. Semigroup a => a -> a -> a
<> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap forall (f :: * -> *) a. HasName f => Char -> Mod f a
Options.short Maybe Char
c
                       forall a. Semigroup a => a -> a -> a
<> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap forall (f :: * -> *) a. HasValue f => a -> Mod f a
Options.value (Maybe String
d forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a. ReadM a -> String -> Maybe a
runReadM forall a. ParseField a => ReadM a
readField)
                       forall a. Semigroup a => a -> a -> a
<> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (forall a (f :: * -> *). (a -> String) -> Mod f a
Options.showDefaultWith forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. a -> b -> a
const) Maybe String
d
                forall a. ReadM a -> Mod OptionFields a -> Parser a
Options.option   forall a. ParseField a => ReadM a
readField Mod OptionFields a
fs

    {-| The only reason for this method is to provide a special case for
        handling `String`s.  All other instances should just fall back on the
        default implementation for `parseListOfField`
    -}
    parseListOfField
        :: Maybe Text
        -- ^ Help message
        -> Maybe Text
        -- ^ Field label
        -> Maybe Char
        -- ^ Short name
        -> Maybe String
        -- ^ Default value
        -> Parser [a]
    parseListOfField Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d = forall (f :: * -> *) a. Alternative f => f a -> f [a]
many (forall a.
ParseField a =>
Maybe Text -> Maybe Text -> Maybe Char -> Maybe String -> Parser a
parseField Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d)

    readField :: ReadM a
    default readField :: Read a => ReadM a
    readField = forall a. Read a => ReadM a
auto

    metavar :: proxy a -> String
    default metavar :: Typeable a => proxy a -> String
    metavar proxy a
_ = forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toUpper (forall a. Show a => a -> String
show (forall a. Typeable a => a -> TypeRep
Data.Typeable.typeOf (forall a. HasCallStack => a
undefined :: a)))

-- | a readMaybe using provided ReadM
runReadM :: ReadM a -> String -> Maybe a
runReadM :: forall a. ReadM a -> String -> Maybe a
runReadM ReadM a
r String
s = forall a c b. (a -> c) -> (b -> c) -> Either a b -> c
either (forall a b. a -> b -> a
const forall a. Maybe a
Nothing) forall a. a -> Maybe a
Just forall a b. (a -> b) -> a -> b
$
    forall e a. Except e a -> Either e a
runExcept (forall r (m :: * -> *) a. ReaderT r m a -> r -> m a
runReaderT (forall a. ReadM a -> ReaderT String (Except ParseError) a
Options.unReadM ReadM a
r) String
s)

instance ParseField Bool
instance ParseField Double
instance ParseField Float
instance ParseField Integer
instance ParseField Ordering
instance ParseField ()
instance ParseField Void

readIntegralBounded :: forall a. (Integral a, Bounded a, Typeable a, ParseField a) => ReadM a
readIntegralBounded :: forall a.
(Integral a, Bounded a, Typeable a, ParseField a) =>
ReadM a
readIntegralBounded =
    forall a. Read a => ReadM a
auto forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Integer -> ReadM a
f
    where
        f :: Integer -> ReadM a
f Integer
i | Integer
i forall a. Ord a => a -> a -> Bool
< Integer
lower = forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
msg
            | Integer
i forall a. Ord a => a -> a -> Bool
> Integer
upper = forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
msg
            | Bool
otherwise = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. Num a => Integer -> a
fromInteger Integer
i
        lower :: Integer
lower = forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
minBound :: a)
        upper :: Integer
upper = forall a. Integral a => a -> Integer
toInteger (forall a. Bounded a => a
maxBound :: a)
        msg :: String
msg = forall a (proxy :: * -> *). ParseField a => proxy a -> String
metavar (forall {k} (t :: k). Proxy t
Proxy :: Proxy a) forall a. Semigroup a => a -> a -> a
<>
              String
" must be within the range [" forall a. Semigroup a => a -> a -> a
<>
              forall a. Show a => a -> String
show Integer
lower forall a. Semigroup a => a -> a -> a
<> String
" .. " forall a. Semigroup a => a -> a -> a
<> forall a. Show a => a -> String
show Integer
upper forall a. Semigroup a => a -> a -> a
<> String
"]"

instance ParseField Int    where readField :: ReadM Int
readField = forall a.
(Integral a, Bounded a, Typeable a, ParseField a) =>
ReadM a
readIntegralBounded
instance ParseField Int8   where readField :: ReadM Int8
readField = forall a.
(Integral a, Bounded a, Typeable a, ParseField a) =>
ReadM a
readIntegralBounded
instance ParseField Int16  where readField :: ReadM Int16
readField = forall a.
(Integral a, Bounded a, Typeable a, ParseField a) =>
ReadM a
readIntegralBounded
instance ParseField Int32  where readField :: ReadM Int32
readField = forall a.
(Integral a, Bounded a, Typeable a, ParseField a) =>
ReadM a
readIntegralBounded
instance ParseField Int64  where readField :: ReadM Int64
readField = forall a.
(Integral a, Bounded a, Typeable a, ParseField a) =>
ReadM a
readIntegralBounded
instance ParseField Word8  where readField :: ReadM Word8
readField = forall a.
(Integral a, Bounded a, Typeable a, ParseField a) =>
ReadM a
readIntegralBounded
instance ParseField Word16 where readField :: ReadM Word16
readField = forall a.
(Integral a, Bounded a, Typeable a, ParseField a) =>
ReadM a
readIntegralBounded
instance ParseField Word32 where readField :: ReadM Word32
readField = forall a.
(Integral a, Bounded a, Typeable a, ParseField a) =>
ReadM a
readIntegralBounded
instance ParseField Word64 where readField :: ReadM Word64
readField = forall a.
(Integral a, Bounded a, Typeable a, ParseField a) =>
ReadM a
readIntegralBounded

#if MIN_VERSION_base(4,8,0)
instance ParseField Natural where
    readField :: ReadM Natural
readField =
        forall a. Read a => ReadM a
auto forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall {m :: * -> *} {a}. (MonadFail m, Num a) => Integer -> m a
f
        where
            f :: Integer -> m a
f Integer
i | Integer
i forall a. Ord a => a -> a -> Bool
< Integer
0 = forall (m :: * -> *) a. MonadFail m => String -> m a
fail String
msg
                | Bool
otherwise = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall a b. (a -> b) -> a -> b
$ forall a. Num a => Integer -> a
fromInteger Integer
i
            msg :: String
msg = String
"NATURAL cannot be negative"
#endif

instance ParseField String where
    parseField :: Maybe Text
-> Maybe Text -> Maybe Char -> Maybe String -> Parser String
parseField = String
-> Maybe Text
-> Maybe Text
-> Maybe Char
-> Maybe String
-> Parser String
parseHelpfulString String
"STRING"

instance ParseField Char where
    metavar :: forall (proxy :: * -> *). proxy Char -> String
metavar proxy Char
_ = String
"CHAR"
    readField :: ReadM Char
readField = do
        String
s <- ReadM String
Options.readerAsk
        case String
s of
            [Char
ch] -> forall (m :: * -> *) a. Monad m => a -> m a
return Char
ch
            String
_    -> forall a. ParseError -> ReadM a
Options.readerAbort (Maybe String -> ParseError
Options.ShowHelpText forall a. Maybe a
Nothing)

    parseListOfField :: Maybe Text
-> Maybe Text -> Maybe Char -> Maybe String -> Parser String
parseListOfField = String
-> Maybe Text
-> Maybe Text
-> Maybe Char
-> Maybe String
-> Parser String
parseHelpfulString String
"STRING"

instance ParseField Any where
    metavar :: forall (proxy :: * -> *). proxy Any -> String
metavar proxy Any
_ = String
"ANY"
    parseField :: Maybe Text
-> Maybe Text -> Maybe Char -> Maybe String -> Parser Any
parseField Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d = Bool -> Any
Any forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a.
ParseField a =>
Maybe Text -> Maybe Text -> Maybe Char -> Maybe String -> Parser a
parseField Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d
instance ParseField All where
    metavar :: forall (proxy :: * -> *). proxy All -> String
metavar proxy All
_ = String
"ALL"
    parseField :: Maybe Text
-> Maybe Text -> Maybe Char -> Maybe String -> Parser All
parseField Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d = Bool -> All
All forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a.
ParseField a =>
Maybe Text -> Maybe Text -> Maybe Char -> Maybe String -> Parser a
parseField Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d

parseHelpfulString
    :: String -> Maybe Text -> Maybe Text -> Maybe Char -> Maybe String -> Parser String
parseHelpfulString :: String
-> Maybe Text
-> Maybe Text
-> Maybe Char
-> Maybe String
-> Parser String
parseHelpfulString String
metavar_ Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d =
    case Maybe Text
m of
        Maybe Text
Nothing   -> do
            let fs :: Mod ArgumentFields String
fs =  forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.metavar String
metavar_
                   forall a. Semigroup a => a -> a -> a
<> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (forall (f :: * -> *) a. String -> Mod f a
Options.help forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
Data.Text.unpack) Maybe Text
h
            forall a. ReadM a -> Mod ArgumentFields a -> Parser a
Options.argument forall s. IsString s => ReadM s
Options.str Mod ArgumentFields String
fs
        Just Text
name -> do
            let fs :: Mod OptionFields String
fs =  forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.metavar String
metavar_
                   forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.long (Text -> String
Data.Text.unpack Text
name)
                   forall a. Semigroup a => a -> a -> a
<> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (forall (f :: * -> *) a. String -> Mod f a
Options.help forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
Data.Text.unpack) Maybe Text
h
                   forall a. Semigroup a => a -> a -> a
<> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap forall (f :: * -> *) a. HasName f => Char -> Mod f a
Options.short Maybe Char
c
                   forall a. Semigroup a => a -> a -> a
<> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap ((forall a (f :: * -> *). Show a => Mod f a
Options.showDefault forall a. Semigroup a => a -> a -> a
<>) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. HasValue f => a -> Mod f a
Options.value) Maybe String
d
            forall a. ReadM a -> Mod OptionFields a -> Parser a
Options.option forall s. IsString s => ReadM s
Options.str Mod OptionFields String
fs

instance ParseField Data.Text.Text where
    parseField :: Maybe Text
-> Maybe Text -> Maybe Char -> Maybe String -> Parser Text
parseField Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d = String -> Text
Data.Text.pack forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String
-> Maybe Text
-> Maybe Text
-> Maybe Char
-> Maybe String
-> Parser String
parseHelpfulString String
"TEXT" Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d

instance ParseField Data.ByteString.ByteString where
    parseField :: Maybe Text
-> Maybe Text -> Maybe Char -> Maybe String -> Parser ByteString
parseField Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ByteString
Data.Text.Encoding.encodeUtf8 (forall a.
ParseField a =>
Maybe Text -> Maybe Text -> Maybe Char -> Maybe String -> Parser a
parseField Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d)

instance ParseField Data.Text.Lazy.Text where
    parseField :: Maybe Text
-> Maybe Text -> Maybe Char -> Maybe String -> Parser Text
parseField Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d = String -> Text
Data.Text.Lazy.pack forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> String
-> Maybe Text
-> Maybe Text
-> Maybe Char
-> Maybe String
-> Parser String
parseHelpfulString String
"TEXT" Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d

instance ParseField Data.ByteString.Lazy.ByteString where
    parseField :: Maybe Text
-> Maybe Text -> Maybe Char -> Maybe String -> Parser ByteString
parseField Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Text -> ByteString
Data.Text.Lazy.Encoding.encodeUtf8 (forall a.
ParseField a =>
Maybe Text -> Maybe Text -> Maybe Char -> Maybe String -> Parser a
parseField Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d)

readISO8601Field :: forall a . (ParseField a, ISO8601 a) => ReadM a
readISO8601Field :: forall a. (ParseField a, ISO8601 a) => ReadM a
readISO8601Field = forall a. (String -> Either String a) -> ReadM a
Options.eitherReader String -> Either String a
reader
  where
    reader :: String -> Either String a
reader String
string =
      case forall (m :: * -> *) t. (MonadFail m, ISO8601 t) => String -> m t
ISO8601.iso8601ParseM String
string of
          Maybe a
Nothing -> forall a b. a -> Either a b
Left (String
"expected " forall a. Semigroup a => a -> a -> a
<> forall a (proxy :: * -> *). ParseField a => proxy a -> String
metavar (forall {k} (t :: k). Proxy t
Proxy :: Proxy a))
          Just a
t -> forall a b. b -> Either a b
Right a
t

instance ParseField CalendarDiffDays where
    metavar :: forall (proxy :: * -> *). proxy CalendarDiffDays -> String
metavar proxy CalendarDiffDays
_ = String
"PyYmMdD"

    readField :: ReadM CalendarDiffDays
readField = forall a. (ParseField a, ISO8601 a) => ReadM a
readISO8601Field

instance ParseField Day where
    metavar :: forall (proxy :: * -> *). proxy Day -> String
metavar proxy Day
_ = String
"yyyy-mm-dd"

    readField :: ReadM Day
readField = forall a. (ParseField a, ISO8601 a) => ReadM a
readISO8601Field

instance ParseField UTCTime where
    metavar :: forall (proxy :: * -> *). proxy UTCTime -> String
metavar proxy UTCTime
_ = String
"yyyy-mm-ddThh:mm:ss[.sss]Z"

    readField :: ReadM UTCTime
readField = forall a. (ParseField a, ISO8601 a) => ReadM a
readISO8601Field

instance ParseField CalendarDiffTime where
    metavar :: forall (proxy :: * -> *). proxy CalendarDiffTime -> String
metavar proxy CalendarDiffTime
_ = String
"PyYmMdDThHmMs[.sss]S"

    readField :: ReadM CalendarDiffTime
readField = forall a. (ParseField a, ISO8601 a) => ReadM a
readISO8601Field

instance ParseField TimeZone where
    metavar :: forall (proxy :: * -> *). proxy TimeZone -> String
metavar proxy TimeZone
_ = String
"±hh:mm"

    readField :: ReadM TimeZone
readField = forall a. (ParseField a, ISO8601 a) => ReadM a
readISO8601Field

instance ParseField TimeOfDay where
    metavar :: forall (proxy :: * -> *). proxy TimeOfDay -> String
metavar proxy TimeOfDay
_ = String
"hh:mm:ss[.sss]"

    readField :: ReadM TimeOfDay
readField = forall a. (ParseField a, ISO8601 a) => ReadM a
readISO8601Field

instance ParseField LocalTime where
    metavar :: forall (proxy :: * -> *). proxy LocalTime -> String
metavar proxy LocalTime
_ = String
"yyyy-mm-ddThh:mm:ss[.sss]"

    readField :: ReadM LocalTime
readField = forall a. (ParseField a, ISO8601 a) => ReadM a
readISO8601Field

instance ParseField ZonedTime where
    metavar :: forall (proxy :: * -> *). proxy ZonedTime -> String
metavar proxy ZonedTime
_ = String
"yyyy-mm-ddThh:mm:ss[.sss]±hh:mm"

    readField :: ReadM ZonedTime
readField = forall a. (ParseField a, ISO8601 a) => ReadM a
readISO8601Field

#if MIN_VERSION_filepath(1,4,100)
instance ParseField OsString where
  metavar _ = "PATH"
  readField = Options.eitherReader reader
    where
      reader string =
        case encodeUtf string of
            Left err -> Left ("Invalid PATH: " ++ show err)
            Right t -> pure t

#endif

{-| A class for all types that can be parsed from zero or more arguments/options
    on the command line

    `parseFields` has a default implementation for any type that implements
    `ParseField`
-}
class ParseRecord a => ParseFields a where
    parseFields
        :: Maybe Text
        -- ^ Help message
        -> Maybe Text
        -- ^ Field label
        -> Maybe Char
        -- ^ Short name
        -> Maybe String
        -- ^ Default value
        -> Parser a
    default parseFields
        :: ParseField a => Maybe Text -> Maybe Text -> Maybe Char -> Maybe String -> Parser a
    parseFields = forall a.
ParseField a =>
Maybe Text -> Maybe Text -> Maybe Char -> Maybe String -> Parser a
parseField

instance ParseFields Char
instance ParseFields Double
instance ParseFields Float
instance ParseFields Int
instance ParseFields Int8
instance ParseFields Int16
instance ParseFields Int32
instance ParseFields Int64
instance ParseFields Integer
instance ParseFields Ordering
instance ParseFields Void
instance ParseFields Word8
instance ParseFields Word16
instance ParseFields Word32
instance ParseFields Word64
instance ParseFields Data.ByteString.ByteString
instance ParseFields Data.ByteString.Lazy.ByteString
instance ParseFields Data.Text.Text
instance ParseFields Data.Text.Lazy.Text
instance ParseFields CalendarDiffDays
instance ParseFields Day
instance ParseFields UTCTime
instance ParseFields CalendarDiffTime
instance ParseFields TimeZone
instance ParseFields TimeOfDay
instance ParseFields LocalTime
instance ParseFields ZonedTime

#if MIN_VERSION_filepath(1,4,100)
instance ParseFields OsString
#endif

#if MIN_VERSION_base(4,8,0)
instance ParseFields Natural
#endif

instance ParseFields Bool where
    parseFields :: Maybe Text
-> Maybe Text -> Maybe Char -> Maybe String -> Parser Bool
parseFields Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d =
        case Maybe Text
m of
            Maybe Text
Nothing   -> do
                let fs :: Mod ArgumentFields Bool
fs =  forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.metavar String
"BOOL"
                       forall a. Semigroup a => a -> a -> a
<> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (forall (f :: * -> *) a. String -> Mod f a
Options.help forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
Data.Text.unpack) Maybe Text
h
                forall a. ReadM a -> Mod ArgumentFields a -> Parser a
Options.argument forall a. Read a => ReadM a
auto Mod ArgumentFields Bool
fs
            Just Text
name -> case Maybe String
d forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall a. Read a => String -> Maybe a
Text.Read.readMaybe of
                Maybe Bool
Nothing -> Mod FlagFields Bool -> Parser Bool
Options.switch forall a b. (a -> b) -> a -> b
$
                  forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.long (Text -> String
Data.Text.unpack Text
name)
                  forall a. Semigroup a => a -> a -> a
<> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (forall (f :: * -> *) a. String -> Mod f a
Options.help forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
Data.Text.unpack) Maybe Text
h
                  forall a. Semigroup a => a -> a -> a
<> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap forall (f :: * -> *) a. HasName f => Char -> Mod f a
Options.short Maybe Char
c
                Just Bool
d0 -> forall a. a -> a -> Mod FlagFields a -> Parser a
Options.flag Bool
d0 (Bool -> Bool
not Bool
d0) forall a b. (a -> b) -> a -> b
$
                  forall (f :: * -> *) a. HasName f => String -> Mod f a
Options.long (Text -> String
Data.Text.unpack Text
name)
                  forall a. Semigroup a => a -> a -> a
<> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap (forall (f :: * -> *) a. String -> Mod f a
Options.help forall b c a. (b -> c) -> (a -> b) -> a -> c
. Text -> String
Data.Text.unpack) Maybe Text
h
                  forall a. Semigroup a => a -> a -> a
<> forall (t :: * -> *) m a.
(Foldable t, Monoid m) =>
(a -> m) -> t a -> m
foldMap forall (f :: * -> *) a. HasName f => Char -> Mod f a
Options.short Maybe Char
c
                 

instance ParseFields () where
    parseFields :: Maybe Text -> Maybe Text -> Maybe Char -> Maybe String -> Parser ()
parseFields Maybe Text
_ Maybe Text
_ Maybe Char
_ Maybe String
_ = forall (f :: * -> *) a. Applicative f => a -> f a
pure ()

instance ParseFields Any where
    parseFields :: Maybe Text
-> Maybe Text -> Maybe Char -> Maybe String -> Parser Any
parseFields Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d = (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Monoid a => [a] -> a
mconcat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Bool -> Any
Any) (forall a.
ParseField a =>
Maybe Text -> Maybe Text -> Maybe Char -> Maybe String -> Parser a
parseField Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d)

instance ParseFields All where
    parseFields :: Maybe Text
-> Maybe Text -> Maybe Char -> Maybe String -> Parser All
parseFields Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d = (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Monoid a => [a] -> a
mconcat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap Bool -> All
All) (forall a.
ParseField a =>
Maybe Text -> Maybe Text -> Maybe Char -> Maybe String -> Parser a
parseField Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d)

instance ParseField a => ParseFields (Maybe a) where
    parseFields :: Maybe Text
-> Maybe Text -> Maybe Char -> Maybe String -> Parser (Maybe a)
parseFields Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d = forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (forall a.
ParseField a =>
Maybe Text -> Maybe Text -> Maybe Char -> Maybe String -> Parser a
parseField Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d)

instance ParseField a => ParseFields (First a) where
    parseFields :: Maybe Text
-> Maybe Text -> Maybe Char -> Maybe String -> Parser (First a)
parseFields Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d = (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Monoid a => [a] -> a
mconcat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. Maybe a -> First a
First forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a
Just)) (forall a.
ParseField a =>
Maybe Text -> Maybe Text -> Maybe Char -> Maybe String -> Parser a
parseField Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d)

instance ParseField a => ParseFields (Last a) where
    parseFields :: Maybe Text
-> Maybe Text -> Maybe Char -> Maybe String -> Parser (Last a)
parseFields Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d = (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Monoid a => [a] -> a
mconcat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. Maybe a -> Last a
Last forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. a -> Maybe a
Just)) (forall a.
ParseField a =>
Maybe Text -> Maybe Text -> Maybe Char -> Maybe String -> Parser a
parseField Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d)

instance (Num a, ParseField a) => ParseFields (Sum a) where
    parseFields :: Maybe Text
-> Maybe Text -> Maybe Char -> Maybe String -> Parser (Sum a)
parseFields Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d = (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Monoid a => [a] -> a
mconcat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. a -> Sum a
Sum) (forall a.
ParseField a =>
Maybe Text -> Maybe Text -> Maybe Char -> Maybe String -> Parser a
parseField Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d)

instance (Num a, ParseField a) => ParseFields (Product a) where
    parseFields :: Maybe Text
-> Maybe Text -> Maybe Char -> Maybe String -> Parser (Product a)
parseFields Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d = (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Monoid a => [a] -> a
mconcat forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a. Alternative f => f a -> f [a]
many forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. a -> Product a
Product) (forall a.
ParseField a =>
Maybe Text -> Maybe Text -> Maybe Char -> Maybe String -> Parser a
parseField Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d)

instance ParseField a => ParseFields [a] where
    parseFields :: Maybe Text
-> Maybe Text -> Maybe Char -> Maybe String -> Parser [a]
parseFields = forall a.
ParseField a =>
Maybe Text
-> Maybe Text -> Maybe Char -> Maybe String -> Parser [a]
parseListOfField

instance ParseField a => ParseFields (NonEmpty a) where
    parseFields :: Maybe Text
-> Maybe Text -> Maybe Char -> Maybe String -> Parser (NonEmpty a)
parseFields Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d = forall a. Parser a -> Parser (NonEmpty a)
Options.NonEmpty.some1 (forall a.
ParseField a =>
Maybe Text -> Maybe Text -> Maybe Char -> Maybe String -> Parser a
parseField Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
d)

{-| Use this to annotate a field with a type-level string (i.e. a `Symbol`)
    representing the help description for that field:

> data Example = Example
>     { foo :: Int    <?> "Documentation for the foo flag"
>     , bar :: Double <?> "Documentation for the bar flag"
>     } deriving (Generic, Show)
-}
newtype (<?>) field (help :: Symbol) = Helpful { forall field (help :: Symbol). (field <?> help) -> field
unHelpful :: field } deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall field (help :: Symbol) x.
Rep (field <?> help) x -> field <?> help
forall field (help :: Symbol) x.
(field <?> help) -> Rep (field <?> help) x
$cto :: forall field (help :: Symbol) x.
Rep (field <?> help) x -> field <?> help
$cfrom :: forall field (help :: Symbol) x.
(field <?> help) -> Rep (field <?> help) x
Generic, Int -> (field <?> help) -> ShowS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall field (help :: Symbol).
Show field =>
Int -> (field <?> help) -> ShowS
forall field (help :: Symbol).
Show field =>
[field <?> help] -> ShowS
forall field (help :: Symbol).
Show field =>
(field <?> help) -> String
showList :: [field <?> help] -> ShowS
$cshowList :: forall field (help :: Symbol).
Show field =>
[field <?> help] -> ShowS
show :: (field <?> help) -> String
$cshow :: forall field (help :: Symbol).
Show field =>
(field <?> help) -> String
showsPrec :: Int -> (field <?> help) -> ShowS
$cshowsPrec :: forall field (help :: Symbol).
Show field =>
Int -> (field <?> help) -> ShowS
Show, (field <?> help) -> DataType
(field <?> help) -> Constr
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall {field} {help :: Symbol}.
(KnownSymbol help, Data field) =>
Typeable (field <?> help)
forall field (help :: Symbol).
(KnownSymbol help, Data field) =>
(field <?> help) -> DataType
forall field (help :: Symbol).
(KnownSymbol help, Data field) =>
(field <?> help) -> Constr
forall field (help :: Symbol).
(KnownSymbol help, Data field) =>
(forall b. Data b => b -> b) -> (field <?> help) -> field <?> help
forall field (help :: Symbol) u.
(KnownSymbol help, Data field) =>
Int -> (forall d. Data d => d -> u) -> (field <?> help) -> u
forall field (help :: Symbol) u.
(KnownSymbol help, Data field) =>
(forall d. Data d => d -> u) -> (field <?> help) -> [u]
forall field (help :: Symbol) r r'.
(KnownSymbol help, Data field) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> (field <?> help) -> r
forall field (help :: Symbol) r r'.
(KnownSymbol help, Data field) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> (field <?> help) -> r
forall field (help :: Symbol) (m :: * -> *).
(KnownSymbol help, Data field, Monad m) =>
(forall d. Data d => d -> m d)
-> (field <?> help) -> m (field <?> help)
forall field (help :: Symbol) (m :: * -> *).
(KnownSymbol help, Data field, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> (field <?> help) -> m (field <?> help)
forall field (help :: Symbol) (c :: * -> *).
(KnownSymbol help, Data field) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (field <?> help)
forall field (help :: Symbol) (c :: * -> *).
(KnownSymbol help, Data field) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> (field <?> help) -> c (field <?> help)
forall field (help :: Symbol) (t :: * -> *) (c :: * -> *).
(KnownSymbol help, Data field, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (field <?> help))
forall field (help :: Symbol) (t :: * -> * -> *) (c :: * -> *).
(KnownSymbol help, Data field, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (field <?> help))
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (field <?> help)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> (field <?> help) -> c (field <?> help)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> (field <?> help) -> m (field <?> help)
$cgmapMo :: forall field (help :: Symbol) (m :: * -> *).
(KnownSymbol help, Data field, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> (field <?> help) -> m (field <?> help)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> (field <?> help) -> m (field <?> help)
$cgmapMp :: forall field (help :: Symbol) (m :: * -> *).
(KnownSymbol help, Data field, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> (field <?> help) -> m (field <?> help)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> (field <?> help) -> m (field <?> help)
$cgmapM :: forall field (help :: Symbol) (m :: * -> *).
(KnownSymbol help, Data field, Monad m) =>
(forall d. Data d => d -> m d)
-> (field <?> help) -> m (field <?> help)
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> (field <?> help) -> u
$cgmapQi :: forall field (help :: Symbol) u.
(KnownSymbol help, Data field) =>
Int -> (forall d. Data d => d -> u) -> (field <?> help) -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> (field <?> help) -> [u]
$cgmapQ :: forall field (help :: Symbol) u.
(KnownSymbol help, Data field) =>
(forall d. Data d => d -> u) -> (field <?> help) -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> (field <?> help) -> r
$cgmapQr :: forall field (help :: Symbol) r r'.
(KnownSymbol help, Data field) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> (field <?> help) -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> (field <?> help) -> r
$cgmapQl :: forall field (help :: Symbol) r r'.
(KnownSymbol help, Data field) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> (field <?> help) -> r
gmapT :: (forall b. Data b => b -> b) -> (field <?> help) -> field <?> help
$cgmapT :: forall field (help :: Symbol).
(KnownSymbol help, Data field) =>
(forall b. Data b => b -> b) -> (field <?> help) -> field <?> help
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (field <?> help))
$cdataCast2 :: forall field (help :: Symbol) (t :: * -> * -> *) (c :: * -> *).
(KnownSymbol help, Data field, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (field <?> help))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (field <?> help))
$cdataCast1 :: forall field (help :: Symbol) (t :: * -> *) (c :: * -> *).
(KnownSymbol help, Data field, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (field <?> help))
dataTypeOf :: (field <?> help) -> DataType
$cdataTypeOf :: forall field (help :: Symbol).
(KnownSymbol help, Data field) =>
(field <?> help) -> DataType
toConstr :: (field <?> help) -> Constr
$ctoConstr :: forall field (help :: Symbol).
(KnownSymbol help, Data field) =>
(field <?> help) -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (field <?> help)
$cgunfold :: forall field (help :: Symbol) (c :: * -> *).
(KnownSymbol help, Data field) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (field <?> help)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> (field <?> help) -> c (field <?> help)
$cgfoldl :: forall field (help :: Symbol) (c :: * -> *).
(KnownSymbol help, Data field) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> (field <?> help) -> c (field <?> help)
Data, (field <?> help) -> (field <?> help) -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall field (help :: Symbol).
Eq field =>
(field <?> help) -> (field <?> help) -> Bool
/= :: (field <?> help) -> (field <?> help) -> Bool
$c/= :: forall field (help :: Symbol).
Eq field =>
(field <?> help) -> (field <?> help) -> Bool
== :: (field <?> help) -> (field <?> help) -> Bool
$c== :: forall field (help :: Symbol).
Eq field =>
(field <?> help) -> (field <?> help) -> Bool
Eq)

instance (ParseField a, KnownSymbol h) => ParseField (a <?> h) where
    parseField :: Maybe Text
-> Maybe Text -> Maybe Char -> Maybe String -> Parser (a <?> h)
parseField Maybe Text
_ Maybe Text
m Maybe Char
c Maybe String
d = forall field (help :: Symbol). field -> field <?> help
Helpful forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
      forall a.
ParseField a =>
Maybe Text -> Maybe Text -> Maybe Char -> Maybe String -> Parser a
parseField ((forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Data.Text.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
.forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal) (forall {k} (t :: k). Proxy t
Proxy :: Proxy h)) Maybe Text
m Maybe Char
c Maybe String
d
    readField :: ReadM (a <?> h)
readField = forall field (help :: Symbol). field -> field <?> help
Helpful forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. ParseField a => ReadM a
readField
    metavar :: forall (proxy :: * -> *). proxy (a <?> h) -> String
metavar proxy (a <?> h)
_ = forall a (proxy :: * -> *). ParseField a => proxy a -> String
metavar (forall {k} (t :: k). Proxy t
Proxy :: Proxy a)

instance (ParseFields a, KnownSymbol h) => ParseFields (a <?> h) where
    parseFields :: Maybe Text
-> Maybe Text -> Maybe Char -> Maybe String -> Parser (a <?> h)
parseFields Maybe Text
_ Maybe Text
m Maybe Char
c Maybe String
d = forall field (help :: Symbol). field -> field <?> help
Helpful forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$>
      forall a.
ParseFields a =>
Maybe Text -> Maybe Text -> Maybe Char -> Maybe String -> Parser a
parseFields ((forall a. a -> Maybe a
Just forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Text
Data.Text.pack forall b c a. (b -> c) -> (a -> b) -> a -> c
.forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal) (forall {k} (t :: k). Proxy t
Proxy :: Proxy h)) Maybe Text
m Maybe Char
c Maybe String
d
instance (ParseFields a, KnownSymbol h) => ParseRecord (a <?> h)

{-| Use this to annotate a field with a type-level string (i.e. a `Symbol`)
    representing the default value for that field:

> data Example = Example
>     { foo :: Int    <!> "1"
>     , bar :: Double <!> "0.5"
>     } deriving (Generic, Show)
-}
newtype (<!>) field (value :: Symbol) = DefValue { forall field (value :: Symbol). (field <!> value) -> field
unDefValue :: field } deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall field (value :: Symbol) x.
Rep (field <!> value) x -> field <!> value
forall field (value :: Symbol) x.
(field <!> value) -> Rep (field <!> value) x
$cto :: forall field (value :: Symbol) x.
Rep (field <!> value) x -> field <!> value
$cfrom :: forall field (value :: Symbol) x.
(field <!> value) -> Rep (field <!> value) x
Generic, Int -> (field <!> value) -> ShowS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall field (value :: Symbol).
Show field =>
Int -> (field <!> value) -> ShowS
forall field (value :: Symbol).
Show field =>
[field <!> value] -> ShowS
forall field (value :: Symbol).
Show field =>
(field <!> value) -> String
showList :: [field <!> value] -> ShowS
$cshowList :: forall field (value :: Symbol).
Show field =>
[field <!> value] -> ShowS
show :: (field <!> value) -> String
$cshow :: forall field (value :: Symbol).
Show field =>
(field <!> value) -> String
showsPrec :: Int -> (field <!> value) -> ShowS
$cshowsPrec :: forall field (value :: Symbol).
Show field =>
Int -> (field <!> value) -> ShowS
Show, (field <!> value) -> DataType
(field <!> value) -> Constr
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall {field} {value :: Symbol}.
(KnownSymbol value, Data field) =>
Typeable (field <!> value)
forall field (value :: Symbol).
(KnownSymbol value, Data field) =>
(field <!> value) -> DataType
forall field (value :: Symbol).
(KnownSymbol value, Data field) =>
(field <!> value) -> Constr
forall field (value :: Symbol).
(KnownSymbol value, Data field) =>
(forall b. Data b => b -> b)
-> (field <!> value) -> field <!> value
forall field (value :: Symbol) u.
(KnownSymbol value, Data field) =>
Int -> (forall d. Data d => d -> u) -> (field <!> value) -> u
forall field (value :: Symbol) u.
(KnownSymbol value, Data field) =>
(forall d. Data d => d -> u) -> (field <!> value) -> [u]
forall field (value :: Symbol) r r'.
(KnownSymbol value, Data field) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> (field <!> value) -> r
forall field (value :: Symbol) r r'.
(KnownSymbol value, Data field) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> (field <!> value) -> r
forall field (value :: Symbol) (m :: * -> *).
(KnownSymbol value, Data field, Monad m) =>
(forall d. Data d => d -> m d)
-> (field <!> value) -> m (field <!> value)
forall field (value :: Symbol) (m :: * -> *).
(KnownSymbol value, Data field, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> (field <!> value) -> m (field <!> value)
forall field (value :: Symbol) (c :: * -> *).
(KnownSymbol value, Data field) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (field <!> value)
forall field (value :: Symbol) (c :: * -> *).
(KnownSymbol value, Data field) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> (field <!> value) -> c (field <!> value)
forall field (value :: Symbol) (t :: * -> *) (c :: * -> *).
(KnownSymbol value, Data field, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (field <!> value))
forall field (value :: Symbol) (t :: * -> * -> *) (c :: * -> *).
(KnownSymbol value, Data field, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (field <!> value))
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (field <!> value)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> (field <!> value) -> c (field <!> value)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> (field <!> value) -> m (field <!> value)
$cgmapMo :: forall field (value :: Symbol) (m :: * -> *).
(KnownSymbol value, Data field, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> (field <!> value) -> m (field <!> value)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> (field <!> value) -> m (field <!> value)
$cgmapMp :: forall field (value :: Symbol) (m :: * -> *).
(KnownSymbol value, Data field, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> (field <!> value) -> m (field <!> value)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> (field <!> value) -> m (field <!> value)
$cgmapM :: forall field (value :: Symbol) (m :: * -> *).
(KnownSymbol value, Data field, Monad m) =>
(forall d. Data d => d -> m d)
-> (field <!> value) -> m (field <!> value)
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> (field <!> value) -> u
$cgmapQi :: forall field (value :: Symbol) u.
(KnownSymbol value, Data field) =>
Int -> (forall d. Data d => d -> u) -> (field <!> value) -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> (field <!> value) -> [u]
$cgmapQ :: forall field (value :: Symbol) u.
(KnownSymbol value, Data field) =>
(forall d. Data d => d -> u) -> (field <!> value) -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> (field <!> value) -> r
$cgmapQr :: forall field (value :: Symbol) r r'.
(KnownSymbol value, Data field) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> (field <!> value) -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> (field <!> value) -> r
$cgmapQl :: forall field (value :: Symbol) r r'.
(KnownSymbol value, Data field) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> (field <!> value) -> r
gmapT :: (forall b. Data b => b -> b)
-> (field <!> value) -> field <!> value
$cgmapT :: forall field (value :: Symbol).
(KnownSymbol value, Data field) =>
(forall b. Data b => b -> b)
-> (field <!> value) -> field <!> value
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (field <!> value))
$cdataCast2 :: forall field (value :: Symbol) (t :: * -> * -> *) (c :: * -> *).
(KnownSymbol value, Data field, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (field <!> value))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (field <!> value))
$cdataCast1 :: forall field (value :: Symbol) (t :: * -> *) (c :: * -> *).
(KnownSymbol value, Data field, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (field <!> value))
dataTypeOf :: (field <!> value) -> DataType
$cdataTypeOf :: forall field (value :: Symbol).
(KnownSymbol value, Data field) =>
(field <!> value) -> DataType
toConstr :: (field <!> value) -> Constr
$ctoConstr :: forall field (value :: Symbol).
(KnownSymbol value, Data field) =>
(field <!> value) -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (field <!> value)
$cgunfold :: forall field (value :: Symbol) (c :: * -> *).
(KnownSymbol value, Data field) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (field <!> value)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> (field <!> value) -> c (field <!> value)
$cgfoldl :: forall field (value :: Symbol) (c :: * -> *).
(KnownSymbol value, Data field) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> (field <!> value) -> c (field <!> value)
Data, (field <!> value) -> (field <!> value) -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall field (value :: Symbol).
Eq field =>
(field <!> value) -> (field <!> value) -> Bool
/= :: (field <!> value) -> (field <!> value) -> Bool
$c/= :: forall field (value :: Symbol).
Eq field =>
(field <!> value) -> (field <!> value) -> Bool
== :: (field <!> value) -> (field <!> value) -> Bool
$c== :: forall field (value :: Symbol).
Eq field =>
(field <!> value) -> (field <!> value) -> Bool
Eq)

instance (ParseField a, KnownSymbol d) => ParseField (a <!> d) where
    parseField :: Maybe Text
-> Maybe Text -> Maybe Char -> Maybe String -> Parser (a <!> d)
parseField Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
_ = forall field (value :: Symbol). field -> field <!> value
DefValue forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a.
ParseField a =>
Maybe Text -> Maybe Text -> Maybe Char -> Maybe String -> Parser a
parseField Maybe Text
h Maybe Text
m Maybe Char
c (forall a. a -> Maybe a
Just (forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (forall {k} (t :: k). Proxy t
Proxy :: Proxy d)))
    readField :: ReadM (a <!> d)
readField = forall field (value :: Symbol). field -> field <!> value
DefValue forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. ParseField a => ReadM a
readField
    metavar :: forall (proxy :: * -> *). proxy (a <!> d) -> String
metavar proxy (a <!> d)
_ = forall a (proxy :: * -> *). ParseField a => proxy a -> String
metavar (forall {k} (t :: k). Proxy t
Proxy :: Proxy a)

instance (ParseFields a, KnownSymbol d) => ParseFields (a <!> d) where
    parseFields :: Maybe Text
-> Maybe Text -> Maybe Char -> Maybe String -> Parser (a <!> d)
parseFields Maybe Text
h Maybe Text
m Maybe Char
c Maybe String
_ = forall field (value :: Symbol). field -> field <!> value
DefValue forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a.
ParseFields a =>
Maybe Text -> Maybe Text -> Maybe Char -> Maybe String -> Parser a
parseFields Maybe Text
h Maybe Text
m Maybe Char
c (forall a. a -> Maybe a
Just (forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (forall {k} (t :: k). Proxy t
Proxy :: Proxy d)))
instance (ParseFields a, KnownSymbol h) => ParseRecord (a <!> h)

{-| Use this to annotate a field with a type-level char (i.e. a `Symbol`)
    representing the short name of the field (only the first character of the
    symbol is used):

> data Example = Example
>     { foo :: Int    <#> "f"
>     , bar :: Double <#> "b"
>     } deriving (Generic, Show)
-}
newtype (<#>) field (value :: Symbol) = ShortName { forall field (value :: Symbol). (field <#> value) -> field
unShortName :: field } deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall field (value :: Symbol) x.
Rep (field <#> value) x -> field <#> value
forall field (value :: Symbol) x.
(field <#> value) -> Rep (field <#> value) x
$cto :: forall field (value :: Symbol) x.
Rep (field <#> value) x -> field <#> value
$cfrom :: forall field (value :: Symbol) x.
(field <#> value) -> Rep (field <#> value) x
Generic, Int -> (field <#> value) -> ShowS
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
forall field (value :: Symbol).
Show field =>
Int -> (field <#> value) -> ShowS
forall field (value :: Symbol).
Show field =>
[field <#> value] -> ShowS
forall field (value :: Symbol).
Show field =>
(field <#> value) -> String
showList :: [field <#> value] -> ShowS
$cshowList :: forall field (value :: Symbol).
Show field =>
[field <#> value] -> ShowS
show :: (field <#> value) -> String
$cshow :: forall field (value :: Symbol).
Show field =>
(field <#> value) -> String
showsPrec :: Int -> (field <#> value) -> ShowS
$cshowsPrec :: forall field (value :: Symbol).
Show field =>
Int -> (field <#> value) -> ShowS
Show, (field <#> value) -> DataType
(field <#> value) -> Constr
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall {field} {value :: Symbol}.
(KnownSymbol value, Data field) =>
Typeable (field <#> value)
forall field (value :: Symbol).
(KnownSymbol value, Data field) =>
(field <#> value) -> DataType
forall field (value :: Symbol).
(KnownSymbol value, Data field) =>
(field <#> value) -> Constr
forall field (value :: Symbol).
(KnownSymbol value, Data field) =>
(forall b. Data b => b -> b)
-> (field <#> value) -> field <#> value
forall field (value :: Symbol) u.
(KnownSymbol value, Data field) =>
Int -> (forall d. Data d => d -> u) -> (field <#> value) -> u
forall field (value :: Symbol) u.
(KnownSymbol value, Data field) =>
(forall d. Data d => d -> u) -> (field <#> value) -> [u]
forall field (value :: Symbol) r r'.
(KnownSymbol value, Data field) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> (field <#> value) -> r
forall field (value :: Symbol) r r'.
(KnownSymbol value, Data field) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> (field <#> value) -> r
forall field (value :: Symbol) (m :: * -> *).
(KnownSymbol value, Data field, Monad m) =>
(forall d. Data d => d -> m d)
-> (field <#> value) -> m (field <#> value)
forall field (value :: Symbol) (m :: * -> *).
(KnownSymbol value, Data field, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> (field <#> value) -> m (field <#> value)
forall field (value :: Symbol) (c :: * -> *).
(KnownSymbol value, Data field) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (field <#> value)
forall field (value :: Symbol) (c :: * -> *).
(KnownSymbol value, Data field) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> (field <#> value) -> c (field <#> value)
forall field (value :: Symbol) (t :: * -> *) (c :: * -> *).
(KnownSymbol value, Data field, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (field <#> value))
forall field (value :: Symbol) (t :: * -> * -> *) (c :: * -> *).
(KnownSymbol value, Data field, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (field <#> value))
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (field <#> value)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> (field <#> value) -> c (field <#> value)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> (field <#> value) -> m (field <#> value)
$cgmapMo :: forall field (value :: Symbol) (m :: * -> *).
(KnownSymbol value, Data field, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> (field <#> value) -> m (field <#> value)
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d)
-> (field <#> value) -> m (field <#> value)
$cgmapMp :: forall field (value :: Symbol) (m :: * -> *).
(KnownSymbol value, Data field, MonadPlus m) =>
(forall d. Data d => d -> m d)
-> (field <#> value) -> m (field <#> value)
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d)
-> (field <#> value) -> m (field <#> value)
$cgmapM :: forall field (value :: Symbol) (m :: * -> *).
(KnownSymbol value, Data field, Monad m) =>
(forall d. Data d => d -> m d)
-> (field <#> value) -> m (field <#> value)
gmapQi :: forall u.
Int -> (forall d. Data d => d -> u) -> (field <#> value) -> u
$cgmapQi :: forall field (value :: Symbol) u.
(KnownSymbol value, Data field) =>
Int -> (forall d. Data d => d -> u) -> (field <#> value) -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> (field <#> value) -> [u]
$cgmapQ :: forall field (value :: Symbol) u.
(KnownSymbol value, Data field) =>
(forall d. Data d => d -> u) -> (field <#> value) -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> (field <#> value) -> r
$cgmapQr :: forall field (value :: Symbol) r r'.
(KnownSymbol value, Data field) =>
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> (field <#> value) -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> (field <#> value) -> r
$cgmapQl :: forall field (value :: Symbol) r r'.
(KnownSymbol value, Data field) =>
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> (field <#> value) -> r
gmapT :: (forall b. Data b => b -> b)
-> (field <#> value) -> field <#> value
$cgmapT :: forall field (value :: Symbol).
(KnownSymbol value, Data field) =>
(forall b. Data b => b -> b)
-> (field <#> value) -> field <#> value
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (field <#> value))
$cdataCast2 :: forall field (value :: Symbol) (t :: * -> * -> *) (c :: * -> *).
(KnownSymbol value, Data field, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e))
-> Maybe (c (field <#> value))
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (field <#> value))
$cdataCast1 :: forall field (value :: Symbol) (t :: * -> *) (c :: * -> *).
(KnownSymbol value, Data field, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (field <#> value))
dataTypeOf :: (field <#> value) -> DataType
$cdataTypeOf :: forall field (value :: Symbol).
(KnownSymbol value, Data field) =>
(field <#> value) -> DataType
toConstr :: (field <#> value) -> Constr
$ctoConstr :: forall field (value :: Symbol).
(KnownSymbol value, Data field) =>
(field <#> value) -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (field <#> value)
$cgunfold :: forall field (value :: Symbol) (c :: * -> *).
(KnownSymbol value, Data field) =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (field <#> value)
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> (field <#> value) -> c (field <#> value)
$cgfoldl :: forall field (value :: Symbol) (c :: * -> *).
(KnownSymbol value, Data field) =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> (field <#> value) -> c (field <#> value)
Data, (field <#> value) -> (field <#> value) -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
forall field (value :: Symbol).
Eq field =>
(field <#> value) -> (field <#> value) -> Bool
/= :: (field <#> value) -> (field <#> value) -> Bool
$c/= :: forall field (value :: Symbol).
Eq field =>
(field <#> value) -> (field <#> value) -> Bool
== :: (field <#> value) -> (field <#> value) -> Bool
$c== :: forall field (value :: Symbol).
Eq field =>
(field <#> value) -> (field <#> value) -> Bool
Eq)

instance (ParseField a, KnownSymbol c) => ParseField (a <#> c) where
    parseField :: Maybe Text
-> Maybe Text -> Maybe Char -> Maybe String -> Parser (a <#> c)
parseField Maybe Text
h Maybe Text
m Maybe Char
_ Maybe String
d = forall field (value :: Symbol). field -> field <#> value
ShortName forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a.
ParseField a =>
Maybe Text -> Maybe Text -> Maybe Char -> Maybe String -> Parser a
parseField Maybe Text
h Maybe Text
m (forall a. [a] -> Maybe a
listToMaybe (forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (forall {k} (t :: k). Proxy t
Proxy :: Proxy c))) Maybe String
d
    readField :: ReadM (a <#> c)
readField = forall field (value :: Symbol). field -> field <#> value
ShortName forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a. ParseField a => ReadM a
readField
    metavar :: forall (proxy :: * -> *). proxy (a <#> c) -> String
metavar proxy (a <#> c)
_ = forall a (proxy :: * -> *). ParseField a => proxy a -> String
metavar (forall {k} (t :: k). Proxy t
Proxy :: Proxy a)

instance (ParseFields a, KnownSymbol c) => ParseFields (a <#> c) where
    parseFields :: Maybe Text
-> Maybe Text -> Maybe Char -> Maybe String -> Parser (a <#> c)
parseFields Maybe Text
h Maybe Text
m Maybe Char
_ Maybe String
d = forall field (value :: Symbol). field -> field <#> value
ShortName forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall a.
ParseFields a =>
Maybe Text -> Maybe Text -> Maybe Char -> Maybe String -> Parser a
parseFields Maybe Text
h Maybe Text
m (forall a. [a] -> Maybe a
listToMaybe (forall (n :: Symbol) (proxy :: Symbol -> *).
KnownSymbol n =>
proxy n -> String
symbolVal (forall {k} (t :: k). Proxy t
Proxy :: Proxy c))) Maybe String
d
instance (ParseFields a, KnownSymbol h) => ParseRecord (a <#> h)

{-| A 1-tuple, used solely to translate `ParseFields` instances into
    `ParseRecord` instances
-}
newtype Only_ a = Only_ a deriving (forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
forall a x. Rep (Only_ a) x -> Only_ a
forall a x. Only_ a -> Rep (Only_ a) x
$cto :: forall a x. Rep (Only_ a) x -> Only_ a
$cfrom :: forall a x. Only_ a -> Rep (Only_ a) x
Generic, Int -> Only_ a -> ShowS
forall a. Show a => Int -> Only_ a -> ShowS
forall a. Show a => [Only_ a] -> ShowS
forall a. Show a => Only_ a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [Only_ a] -> ShowS
$cshowList :: forall a. Show a => [Only_ a] -> ShowS
show :: Only_ a -> String
$cshow :: forall a. Show a => Only_ a -> String
showsPrec :: Int -> Only_ a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> Only_ a -> ShowS
Show)

{-| This is a convenience function that you can use if you want to create a
    `ParseRecord` instance that just defers to the `ParseFields` instance for
    the same type:

> instance ParseRecord MyType where
>     parseRecord = fmap getOnly parseRecord
-}
getOnly :: Only a -> a
getOnly :: forall a. Only a -> a
getOnly (Only a
x) = a
x

{-| A class for types that can be parsed from the command line

    This class has a default implementation for any type that implements
    `Generic` and you can derive `Generic` for many types by enabling the
    @DeriveGeneric@ language extension

    You can also use `getOnly` to create a `ParseRecord` instance from a
    `ParseFields` instance:

> instance ParseRecord MyType where
>     parseRecord = fmap getOnly parseRecord
-}
class ParseRecord a where
    parseRecord :: Parser a
    default parseRecord :: (Generic a, GenericParseRecord (Rep a)) => Parser a
    parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a x. Generic a => Rep a x -> a
GHC.Generics.to (forall (f :: * -> *) p.
GenericParseRecord f =>
Modifiers -> Parser (f p)
genericParseRecord Modifiers
defaultModifiers)

instance ParseFields a => ParseRecord (Only_ a)
instance ParseFields a => ParseRecord (Only a) where
    parseRecord :: Parser (Only a)
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall {a}. Only_ a -> Only a
adapt forall a. ParseRecord a => Parser a
parseRecord
      where
        adapt :: Only_ a -> Only a
adapt (Only_ a
x) = forall a. a -> Only a
Only a
x

instance ParseRecord Char where
    parseRecord :: Parser Char
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord
instance ParseRecord Double where
    parseRecord :: Parser Double
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord
instance ParseRecord Float where
    parseRecord :: Parser Float
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord
instance ParseRecord Int where
    parseRecord :: Parser Int
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord
instance ParseRecord Int8 where
    parseRecord :: Parser Int8
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord
instance ParseRecord Int16 where
    parseRecord :: Parser Int16
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord
instance ParseRecord Int32 where
    parseRecord :: Parser Int32
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord
instance ParseRecord Int64 where
    parseRecord :: Parser Int64
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord
instance ParseRecord Ordering
instance ParseRecord Void
instance ParseRecord Word8 where
    parseRecord :: Parser Word8
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord
instance ParseRecord Word16 where
    parseRecord :: Parser Word16
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord
instance ParseRecord Word32 where
    parseRecord :: Parser Word32
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord
instance ParseRecord Word64 where
    parseRecord :: Parser Word64
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord
instance ParseRecord ()

#if MIN_VERSION_base(4,8,0)
instance ParseRecord Natural where
    parseRecord :: Parser Natural
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord
#endif

instance ParseRecord Bool where
    parseRecord :: Parser Bool
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord

instance ParseRecord Integer where
    parseRecord :: Parser Integer
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord

instance ParseRecord Data.Text.Text where
    parseRecord :: Parser Text
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord

instance ParseRecord Data.Text.Lazy.Text where
    parseRecord :: Parser Text
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord

instance ParseRecord Any where
    parseRecord :: Parser Any
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord

instance ParseRecord All where
    parseRecord :: Parser All
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord

instance ParseRecord Data.ByteString.ByteString where
    parseRecord :: Parser ByteString
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord

instance ParseRecord Data.ByteString.Lazy.ByteString where
    parseRecord :: Parser ByteString
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord

instance ParseRecord CalendarDiffDays where
    parseRecord :: Parser CalendarDiffDays
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord

instance ParseRecord Day where
    parseRecord :: Parser Day
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord

instance ParseRecord UTCTime where
    parseRecord :: Parser UTCTime
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord

instance ParseRecord CalendarDiffTime where
    parseRecord :: Parser CalendarDiffTime
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord

instance ParseRecord TimeZone where
    parseRecord :: Parser TimeZone
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord

instance ParseRecord TimeOfDay where
    parseRecord :: Parser TimeOfDay
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord

instance ParseRecord LocalTime where
    parseRecord :: Parser LocalTime
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord

instance ParseRecord ZonedTime where
    parseRecord :: Parser ZonedTime
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord

#if MIN_VERSION_filepath(1,4,100)
instance ParseRecord OsString where
    parseRecord = fmap getOnly parseRecord
#endif

instance ParseField a => ParseRecord (Maybe a) where
    parseRecord :: Parser (Maybe a)
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord

instance ParseField a => ParseRecord (First a) where
    parseRecord :: Parser (First a)
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord

instance ParseField a => ParseRecord (Last a) where
    parseRecord :: Parser (Last a)
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord

instance (Num a, ParseField a) => ParseRecord (Sum a) where
    parseRecord :: Parser (Sum a)
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord

instance (Num a, ParseField a) => ParseRecord (Product a) where
    parseRecord :: Parser (Product a)
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord

instance ParseField a => ParseRecord [a] where
    parseRecord :: Parser [a]
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord

instance ParseField a => ParseRecord (NonEmpty a) where
    parseRecord :: Parser (NonEmpty a)
parseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a. Only a -> a
getOnly forall a. ParseRecord a => Parser a
parseRecord

instance (ParseFields a, ParseFields b) => ParseRecord (a, b)
instance (ParseFields a, ParseFields b, ParseFields c) => ParseRecord (a, b, c)
instance (ParseFields a, ParseFields b, ParseFields c, ParseFields d) => ParseRecord (a, b, c, d)
instance (ParseFields a, ParseFields b, ParseFields c, ParseFields d, ParseFields e) => ParseRecord (a, b, c, d, e)
instance (ParseFields a, ParseFields b, ParseFields c, ParseFields d, ParseFields e, ParseFields f) => ParseRecord (a, b, c, d, e, f)
instance (ParseFields a, ParseFields b, ParseFields c, ParseFields d, ParseFields e, ParseFields f, ParseFields g) => ParseRecord (a, b, c, d, e, f, g)

instance (ParseFields a, ParseFields b) => ParseRecord (Either a b)

{-| Options for customizing derived `ParseRecord` implementations for `Generic`
    types

    You can either create the `Modifiers` record directly:

    > modifiers :: Modifiers
    > modifiers = Modifiers
    >     { fieldNameModifier       = ...
    >     , constructorNameModifier = ...
    >     , shortNameModifier       = ...
    >     }

    ... or you can tweak the `defaultModifiers`:

    > modifiers :: Modifiers
    > modifiers = defaultModifiers { fieldNameModifier = ... }

    ... or you can use/tweak a predefined `Modifier`, like `lispCaseModifiers`

    The `parseRecordWithModifiers` function uses this `Modifiers` record when
    generating a `Generic` implementation of `ParseRecord`
-}
data Modifiers = Modifiers
  { Modifiers -> ShowS
fieldNameModifier :: String -> String
  -- ^ Transform the name of derived fields (Default: @id@)
  , Modifiers -> ShowS
constructorNameModifier :: String -> String
  -- ^ Transform the name of derived constructors (Default: @map toLower@)
  , Modifiers -> String -> Maybe Char
shortNameModifier :: String -> Maybe Char
  -- ^ Derives an optional short name from the field name (Default: @\\_ -> Nothing@)
  }

{-| These are the default modifiers used if you derive a `Generic`
    implementation.  You can customize this and pass the result to
    `parseRecordWithModifiers` if you would like to modify the derived
    implementation:

    > myModifiers :: Modifiers
    > myModifiers = defaultModifiers { constructorNameModifier = id }
    >
    > instance ParseRecord MyType where
    >     parseRecord = parseRecordWithModifiers myModifiers
-}
defaultModifiers :: Modifiers
defaultModifiers :: Modifiers
defaultModifiers = Modifiers
    { fieldNameModifier :: ShowS
fieldNameModifier       = forall a. a -> a
id
    , constructorNameModifier :: ShowS
constructorNameModifier = forall a b. (a -> b) -> [a] -> [b]
map Char -> Char
toLower
    , shortNameModifier :: String -> Maybe Char
shortNameModifier       = \String
_ -> forall a. Maybe a
Nothing
    }

-- | Convert field and constructor names from @CamelCase@ to @lisp-case@.
--
-- Leading underscores are dropped, allowing one to use option names
-- which are Haskell keywords or otherwise conflicting identifiers.
--
-- > BuildCommand -> build-command
-- > someFlag -> --some-flag
-- > _type -> --type
-- > _splitAt -> --split-at
lispCaseModifiers :: Modifiers
lispCaseModifiers :: Modifiers
lispCaseModifiers = ShowS -> ShowS -> (String -> Maybe Char) -> Modifiers
Modifiers ShowS
lispCase ShowS
lispCase (\String
_ -> forall a. Maybe a
Nothing)
  where
    lispCase :: ShowS
lispCase = forall a. (a -> Bool) -> [a] -> [a]
dropWhile (forall a. Eq a => a -> a -> Bool
== Char
'-') forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= Char -> String
lower) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. (a -> Bool) -> [a] -> [a]
dropWhile (forall a. Eq a => a -> a -> Bool
== Char
'_')
    lower :: Char -> String
lower Char
c | Char -> Bool
isUpper Char
c = [Char
'-', Char -> Char
toLower Char
c]
            | Bool
otherwise = [Char
c]

{-| Use this for the `shortNameModifier` field of the `Modifiers` record if
    you want to use the first letter of each option as the short name
-}
firstLetter :: String -> Maybe Char
firstLetter :: String -> Maybe Char
firstLetter (Char
c:String
_) = forall a. a -> Maybe a
Just Char
c
firstLetter  String
_    = forall a. Maybe a
Nothing

class GenericParseRecord f where
    genericParseRecord :: Modifiers -> Parser (f p)

instance GenericParseRecord U1 where
    genericParseRecord :: forall p. Modifiers -> Parser (U1 p)
genericParseRecord Modifiers
_ = forall (f :: * -> *) a. Applicative f => a -> f a
pure forall k (p :: k). U1 p
U1

-- See: [NOTE - Sums]
instance GenericParseRecord f => GenericParseRecord (M1 C c f) where
    genericParseRecord :: forall p. Modifiers -> Parser (M1 C c f p)
genericParseRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) p.
GenericParseRecord f =>
Modifiers -> Parser (f p)
genericParseRecord

-- See: [NOTE - Sums]
instance (GenericParseRecord (f :+: g), GenericParseRecord (h :+: i)) => GenericParseRecord ((f :+: g) :+: (h :+: i)) where
    genericParseRecord :: forall p. Modifiers -> Parser ((:+:) (f :+: g) (h :+: i) p)
genericParseRecord Modifiers
mods = do
        forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
L1 (forall (f :: * -> *) p.
GenericParseRecord f =>
Modifiers -> Parser (f p)
genericParseRecord Modifiers
mods) forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
R1 (forall (f :: * -> *) p.
GenericParseRecord f =>
Modifiers -> Parser (f p)
genericParseRecord Modifiers
mods)

-- See: [NOTE - Sums]
instance (Constructor c, GenericParseRecord f, GenericParseRecord (g :+: h)) => GenericParseRecord (M1 C c f :+: (g :+: h)) where
    genericParseRecord :: forall p. Modifiers -> Parser ((:+:) (M1 C c f) (g :+: h) p)
genericParseRecord mods :: Modifiers
mods@Modifiers{ShowS
String -> Maybe Char
shortNameModifier :: String -> Maybe Char
constructorNameModifier :: ShowS
fieldNameModifier :: ShowS
shortNameModifier :: Modifiers -> String -> Maybe Char
constructorNameModifier :: Modifiers -> ShowS
fieldNameModifier :: Modifiers -> ShowS
..} = do
        let m :: M1 i c f a
            m :: forall i a. M1 i c f a
m = forall a. HasCallStack => a
undefined

        let name :: String
name = ShowS
constructorNameModifier (forall {k} (c :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
       (f :: k1 -> *) (a :: k1).
Constructor c =>
t c f a -> String
conName forall i a. M1 i c f a
m)

        let info :: ParserInfo (f p)
info = forall a. Parser a -> InfoMod a -> ParserInfo a
Options.info (forall a. Parser (a -> a)
Options.helper forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall (f :: * -> *) p.
GenericParseRecord f =>
Modifiers -> Parser (f p)
genericParseRecord Modifiers
mods)) forall a. Monoid a => a
mempty

        let subparserFields :: Mod CommandFields (f p)
subparserFields =
                   forall a. String -> ParserInfo a -> Mod CommandFields a
Options.command String
name ParserInfo (f p)
info
                forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.metavar String
name

        let parser :: Parser (f p)
parser = forall a. Mod CommandFields a -> Parser a
Options.subparser Mod CommandFields (f p)
subparserFields

        forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
L1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1) Parser (f p)
parser forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
R1 (forall (f :: * -> *) p.
GenericParseRecord f =>
Modifiers -> Parser (f p)
genericParseRecord Modifiers
mods)

-- See: [NOTE - Sums]
instance (Constructor c, GenericParseRecord (f :+: g), GenericParseRecord h) => GenericParseRecord ((f :+: g) :+: M1 C c h) where
    genericParseRecord :: forall p. Modifiers -> Parser ((:+:) (f :+: g) (M1 C c h) p)
genericParseRecord mods :: Modifiers
mods@Modifiers{ShowS
String -> Maybe Char
shortNameModifier :: String -> Maybe Char
constructorNameModifier :: ShowS
fieldNameModifier :: ShowS
shortNameModifier :: Modifiers -> String -> Maybe Char
constructorNameModifier :: Modifiers -> ShowS
fieldNameModifier :: Modifiers -> ShowS
..} = do
        let m :: M1 i c h a
            m :: forall i a. M1 i c h a
m = forall a. HasCallStack => a
undefined

        let name :: String
name = ShowS
constructorNameModifier (forall {k} (c :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
       (f :: k1 -> *) (a :: k1).
Constructor c =>
t c f a -> String
conName forall i a. M1 i c h a
m)

        let info :: ParserInfo (h p)
info = forall a. Parser a -> InfoMod a -> ParserInfo a
Options.info (forall a. Parser (a -> a)
Options.helper forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall (f :: * -> *) p.
GenericParseRecord f =>
Modifiers -> Parser (f p)
genericParseRecord Modifiers
mods)) forall a. Monoid a => a
mempty

        let subparserFields :: Mod CommandFields (h p)
subparserFields =
                   forall a. String -> ParserInfo a -> Mod CommandFields a
Options.command String
name ParserInfo (h p)
info
                forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.metavar String
name

        let parser :: Parser (h p)
parser = forall a. Mod CommandFields a -> Parser a
Options.subparser Mod CommandFields (h p)
subparserFields

        forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
L1 (forall (f :: * -> *) p.
GenericParseRecord f =>
Modifiers -> Parser (f p)
genericParseRecord Modifiers
mods) forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
R1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1) Parser (h p)
parser

-- See: [NOTE - Sums]
instance (Constructor c1, Constructor c2, GenericParseRecord f1, GenericParseRecord f2) => GenericParseRecord (M1 C c1 f1 :+: M1 C c2 f2) where
    genericParseRecord :: forall p. Modifiers -> Parser ((:+:) (M1 C c1 f1) (M1 C c2 f2) p)
genericParseRecord mods :: Modifiers
mods@Modifiers{ShowS
String -> Maybe Char
shortNameModifier :: String -> Maybe Char
constructorNameModifier :: ShowS
fieldNameModifier :: ShowS
shortNameModifier :: Modifiers -> String -> Maybe Char
constructorNameModifier :: Modifiers -> ShowS
fieldNameModifier :: Modifiers -> ShowS
..} = do
        let m1 :: M1 i c1 f a
            m1 :: forall i (f :: * -> *) a. M1 i c1 f a
m1 = forall a. HasCallStack => a
undefined
        let m2 :: M1 i c2 g a
            m2 :: forall i (g :: * -> *) a. M1 i c2 g a
m2 = forall a. HasCallStack => a
undefined

        let name1 :: String
name1 = ShowS
constructorNameModifier (forall {k} (c :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
       (f :: k1 -> *) (a :: k1).
Constructor c =>
t c f a -> String
conName forall i (f :: * -> *) a. M1 i c1 f a
m1)
        let name2 :: String
name2 = ShowS
constructorNameModifier (forall {k} (c :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
       (f :: k1 -> *) (a :: k1).
Constructor c =>
t c f a -> String
conName forall i (g :: * -> *) a. M1 i c2 g a
m2)

        let info1 :: ParserInfo (f1 p)
info1 = forall a. Parser a -> InfoMod a -> ParserInfo a
Options.info (forall a. Parser (a -> a)
Options.helper forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall (f :: * -> *) p.
GenericParseRecord f =>
Modifiers -> Parser (f p)
genericParseRecord Modifiers
mods)) forall a. Monoid a => a
mempty
        let info2 :: ParserInfo (f2 p)
info2 = forall a. Parser a -> InfoMod a -> ParserInfo a
Options.info (forall a. Parser (a -> a)
Options.helper forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> (forall (f :: * -> *) p.
GenericParseRecord f =>
Modifiers -> Parser (f p)
genericParseRecord Modifiers
mods)) forall a. Monoid a => a
mempty

        let subparserFields1 :: Mod CommandFields (f1 p)
subparserFields1 =
                   forall a. String -> ParserInfo a -> Mod CommandFields a
Options.command String
name1 ParserInfo (f1 p)
info1
                forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.metavar String
name1
        let subparserFields2 :: Mod CommandFields (f2 p)
subparserFields2 =
                   forall a. String -> ParserInfo a -> Mod CommandFields a
Options.command String
name2 ParserInfo (f2 p)
info2
                forall a. Semigroup a => a -> a -> a
<> forall (f :: * -> *) a. HasMetavar f => String -> Mod f a
Options.metavar String
name2

        let parser1 :: Parser (f1 p)
parser1 = forall a. Mod CommandFields a -> Parser a
Options.subparser Mod CommandFields (f1 p)
subparserFields1
        let parser2 :: Parser (f2 p)
parser2 = forall a. Mod CommandFields a -> Parser a
Options.subparser Mod CommandFields (f2 p)
subparserFields2

        forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
L1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1) Parser (f1 p)
parser1 forall (f :: * -> *) a. Alternative f => f a -> f a -> f a
<|> forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
R1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1) Parser (f2 p)
parser2

instance (GenericParseRecord f, GenericParseRecord g) => GenericParseRecord (f :*: g) where
    genericParseRecord :: forall p. Modifiers -> Parser ((:*:) f g p)
genericParseRecord Modifiers
mods = forall (f :: * -> *) a b c.
Applicative f =>
(a -> b -> c) -> f a -> f b -> f c
liftA2 forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
(:*:) (forall (f :: * -> *) p.
GenericParseRecord f =>
Modifiers -> Parser (f p)
genericParseRecord Modifiers
mods) (forall (f :: * -> *) p.
GenericParseRecord f =>
Modifiers -> Parser (f p)
genericParseRecord Modifiers
mods)

instance GenericParseRecord V1 where
    genericParseRecord :: forall p. Modifiers -> Parser (V1 p)
genericParseRecord Modifiers
_ = forall (f :: * -> *) a. Alternative f => f a
empty

instance (Selector s, ParseFields a) => GenericParseRecord (M1 S s (K1 i a)) where
    genericParseRecord :: forall p. Modifiers -> Parser (M1 S s (K1 i a) p)
genericParseRecord Modifiers{ShowS
String -> Maybe Char
shortNameModifier :: String -> Maybe Char
constructorNameModifier :: ShowS
fieldNameModifier :: ShowS
shortNameModifier :: Modifiers -> String -> Maybe Char
constructorNameModifier :: Modifiers -> ShowS
fieldNameModifier :: Modifiers -> ShowS
..} = do
        let m :: M1 i s f a
            m :: forall (f :: * -> *). M1 i s f a
m = forall a. HasCallStack => a
undefined

        let label :: Maybe Text
label = case forall {k} (s :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
       (f :: k1 -> *) (a :: k1).
Selector s =>
t s f a -> String
selName forall (f :: * -> *). M1 i s f a
m of
                String
""   -> forall a. Maybe a
Nothing
                String
name -> forall a. a -> Maybe a
Just (String -> Text
Data.Text.pack (ShowS
fieldNameModifier String
name))
        let shortName :: Maybe Char
shortName = String -> Maybe Char
shortNameModifier (forall {k} (s :: k) k1 (t :: k -> (k1 -> *) -> k1 -> *)
       (f :: k1 -> *) (a :: k1).
Selector s =>
t s f a -> String
selName forall (f :: * -> *). M1 i s f a
m)
        forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k i c (p :: k). c -> K1 i c p
K1) (forall a.
ParseFields a =>
Maybe Text -> Maybe Text -> Maybe Char -> Maybe String -> Parser a
parseFields forall a. Maybe a
Nothing Maybe Text
label Maybe Char
shortName forall a. Maybe a
Nothing)

{- [NOTE - Sums]

   You might wonder why the `GenericParseRecord` instances for `(:+:)` are so
   complicated.  A much simpler approach would be something like this:

> instance (GenericParseRecord f, GenericParseRecord g) => GenericParseRecord (f :+: g) where
>     genericParseRecord = fmap L1 genericParseRecord <|> fmap R1 genericParseRecord
> 
> instance (Constructor c, GenericParseRecord f) => GenericParseRecord (M1 C c f) where
>     genericParseRecord = do
>         let m :: M1 i c f a
>             m = undefined
> 
>         let name = map toLower (conName m)
> 
>         let info = Options.info genericParseRecord mempty
> 
>         let subparserFields =
>                    Options.command n info
>                 <> Options.metavar n
> 
>         fmap M1 (Options.subparser subparserFields)

    The reason for the extra complication is so that datatypes with just one
    constructor don't have subcommands.  That way, if a user defines a data
    type like:

> data Example = Example { foo :: Double } deriving (Generic)
>
> instance ParseRecord Example

    .. then the command line will only read in the @--foo@ flag and won't
    expect a gratuitous @example@ subcommand:

> ./example --foo 2

    However, if a user defines a data type with two constructors then the
    subcommand support will kick in.

    Some other alternatives that I considered and rejected:

    * Alternative #1: Constructors prefixed with something like @Command_@ are
      turned into sub-commands named after the constructor with the prefix
      stripped.  If the prefix is not present then they don't get a subcommand.

        I rejected this approach for several reasons:

        * It's ugly
        * It's error-prone (consider the case: @data T = C1 Int | C2 Int@, which
          would never successfully parse @C2@).  Subcommands should be mandatory
          for types with multiple constructors
        * It doesn't work "out-of-the-box" for most types in the Haskell
          ecosystem which were not written with this library in mind

    * Alternative #2: Any constructor named some reserved name (like @Only@)
      would not generate a sub-command.

        I rejected this approach for a couple of reasons:

        * Too surprising.  The user would never know or guess about this
          behavior without reading the documentation.
        * Doesn't work "out-of-the-box" for single-constructor types in the
          Haskell ecosystem (like `(a, b)`, for example)
-}

instance GenericParseRecord f => GenericParseRecord (M1 D c f) where
    genericParseRecord :: forall p. Modifiers -> Parser (M1 D c f p)
genericParseRecord Modifiers
mods = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 (forall a. Parser (a -> a)
Options.helper forall (f :: * -> *) a b. Applicative f => f (a -> b) -> f a -> f b
<*> forall (f :: * -> *) p.
GenericParseRecord f =>
Modifiers -> Parser (f p)
genericParseRecord Modifiers
mods)

{-| Use `parseRecordWithModifiers` when you want to tweak the behavior of a
    derived `ParseRecord` implementation, like this:

    > myModifiers :: Modifiers
    > myModifiers = defaultModifiers { constructorNameModifier = id }
    >
    > instance ParseRecord MyType where
    >     parseRecord = parseRecordWithModifiers myModifiers

    This will still require that you derive `Generic` for your type to automate
    most of the implementation, but the `Modifiers` that you pass will change
    how the implementation generates the command line interface
-}
parseRecordWithModifiers
    :: (Generic a, GenericParseRecord (Rep a)) => Modifiers -> Parser a
parseRecordWithModifiers :: forall a.
(Generic a, GenericParseRecord (Rep a)) =>
Modifiers -> Parser a
parseRecordWithModifiers Modifiers
mods = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a x. Generic a => Rep a x -> a
GHC.Generics.to (forall (f :: * -> *) p.
GenericParseRecord f =>
Modifiers -> Parser (f p)
genericParseRecord Modifiers
mods)

-- | Marshal any value that implements `ParseRecord` from the command line
--
-- If you need to modify the top-level 'ParserInfo' or 'ParserPrefs'
-- use the 'getRecordWith' function.
getRecord
    :: (MonadIO io, ParseRecord a)
    => Text
    -- ^ Program description
    -> io a
getRecord :: forall (io :: * -> *) a.
(MonadIO io, ParseRecord a) =>
Text -> io a
getRecord Text
desc = forall (io :: * -> *) a.
(MonadIO io, ParseRecord a) =>
InfoMod a -> PrefsMod -> io a
getRecordWith InfoMod a
header forall a. Monoid a => a
mempty
  where
    header :: InfoMod a
header = forall a. String -> InfoMod a
Options.header (Text -> String
Data.Text.unpack Text
desc)

-- | Marshal any value that implements `ParseRecord` from the command line
--
-- This is the lower-level sibling of 'getRecord and lets you modify
-- the 'ParserInfo' and 'ParserPrefs' records.
getRecordWith
    :: (MonadIO io, ParseRecord a)
    => Options.InfoMod a
    -- ^ 'ParserInfo' modifiers
    -> Options.PrefsMod
    -- ^ 'ParserPrefs' modifiers
    -> io a
getRecordWith :: forall (io :: * -> *) a.
(MonadIO io, ParseRecord a) =>
InfoMod a -> PrefsMod -> io a
getRecordWith InfoMod a
infoMods PrefsMod
prefsMods = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (forall a. ParserPrefs -> ParserInfo a -> IO a
Options.customExecParser ParserPrefs
prefs ParserInfo a
info)
  where
    prefs :: ParserPrefs
prefs  = PrefsMod -> ParserPrefs
Options.prefs (PrefsMod
defaultParserPrefs forall a. Semigroup a => a -> a -> a
<> PrefsMod
prefsMods)
    info :: ParserInfo a
info   = forall a. Parser a -> InfoMod a -> ParserInfo a
Options.info forall a. ParseRecord a => Parser a
parseRecord InfoMod a
infoMods

-- | Marshal any value that implements `ParseRecord` from the commmand line
-- alongside an io action that prints the help message.
getWithHelp
    :: (MonadIO io, ParseRecord a)
    => Text
    -- ^ Program description
    -> io (a, io ())
    -- ^ (options, io action to print help message)
getWithHelp :: forall (io :: * -> *) a.
(MonadIO io, ParseRecord a) =>
Text -> io (a, io ())
getWithHelp Text
desc = forall (io :: * -> *) a.
(MonadIO io, ParseRecord a) =>
Text -> PrefsMod -> io (a, io ())
getWithHelpWith Text
desc forall a. Monoid a => a
mempty

-- | Marshal any value that implements `ParseRecord` from the commmand line
-- alongside an io action that prints the help message.
getWithHelpWith
    :: (MonadIO io, ParseRecord a)
    => Text
    -- ^ Program description
    -> Options.PrefsMod
    -- ^ 'ParserPrefs' modifiers
    -> io (a, io ())
    -- ^ (options, io action to print help message)
getWithHelpWith :: forall (io :: * -> *) a.
(MonadIO io, ParseRecord a) =>
Text -> PrefsMod -> io (a, io ())
getWithHelpWith Text
desc PrefsMod
prefsMods  = do
  a
a <- forall (io :: * -> *) a.
(MonadIO io, ParseRecord a) =>
InfoMod a -> PrefsMod -> io a
getRecordWith InfoMod a
header PrefsMod
prefsMods
  forall (m :: * -> *) a. Monad m => a -> m a
return (a
a, io ()
help)
  where
    header :: InfoMod a
header = forall a. String -> InfoMod a
Options.header (Text -> String
Data.Text.unpack Text
desc)
    info :: ParserInfo a
info   = forall a. Parser a -> InfoMod a -> ParserInfo a
Options.info forall a. ParseRecord a => Parser a
parseRecord InfoMod a
header
    help :: io ()
help   = forall (m :: * -> *) a. MonadIO m => IO a -> m a
liftIO (forall a. ParserPrefs -> ParserInfo a -> IO ()
showHelpText (PrefsMod -> ParserPrefs
Options.prefs PrefsMod
defaultParserPrefs) ParserInfo a
info)

{-| Pure version of `getRecord`

If you need to modify the parser's 'ParserInfo' or 'ParserPrefs', use
`getRecordPureWith`.

>>> :set -XOverloadedStrings
>>> getRecordPure ["1"] :: Maybe Int
Just 1
>>> getRecordPure ["1", "2"] :: Maybe [Int]
Just [1,2]
>>> getRecordPure ["Foo"] :: Maybe Int
Nothing
-}
getRecordPure
    :: ParseRecord a
    => [Text]
    -- ^ Command-line arguments
    -> Maybe a
getRecordPure :: forall a. ParseRecord a => [Text] -> Maybe a
getRecordPure [Text]
args = forall a.
ParseRecord a =>
[Text] -> InfoMod a -> PrefsMod -> Maybe a
getRecordPureWith [Text]
args forall a. Monoid a => a
mempty forall a. Monoid a => a
mempty

{-| Pure version of `getRecordWith`

Like `getRecordWith`, this is a sibling of 'getRecordPure and
exposes the monoidal modifier structures for 'ParserInfo' and
'ParserPrefs' to you.

>>> :set -XOverloadedStrings
>>> getRecordPureWith ["1"] mempty mempty :: Maybe Int
Just 1
>>> getRecordPureWith ["1", "2"] mempty mempty :: Maybe [Int]
Just [1,2]
>>> getRecordPureWith ["Foo"] mempty mempty :: Maybe Int
Nothing
-}
getRecordPureWith
    :: ParseRecord a
    => [Text]
    -- ^ Command-line arguments
    -> Options.InfoMod a
    -- ^ 'ParserInfo' modifiers
    -> Options.PrefsMod
    -- ^ 'ParserPrefs' modifiers
    -> Maybe a
getRecordPureWith :: forall a.
ParseRecord a =>
[Text] -> InfoMod a -> PrefsMod -> Maybe a
getRecordPureWith [Text]
args InfoMod a
infoMod PrefsMod
prefsMod = do
    let header :: InfoMod a
header = forall a. String -> InfoMod a
Options.header String
""
    let info :: ParserInfo a
info   = forall a. Parser a -> InfoMod a -> ParserInfo a
Options.info forall a. ParseRecord a => Parser a
parseRecord (forall {a}. InfoMod a
header forall a. Semigroup a => a -> a -> a
<> InfoMod a
infoMod)
    let prefs :: ParserPrefs
prefs  = PrefsMod -> ParserPrefs
Options.prefs (PrefsMod
defaultParserPrefs forall a. Semigroup a => a -> a -> a
<> PrefsMod
prefsMod)
    let args' :: [String]
args'  = forall a b. (a -> b) -> [a] -> [b]
map Text -> String
Data.Text.unpack [Text]
args
    forall a. ParserResult a -> Maybe a
Options.getParseResult (forall a. ParserPrefs -> ParserInfo a -> [String] -> ParserResult a
Options.execParserPure ParserPrefs
prefs ParserInfo a
info [String]
args')

-- | @optparse-generic@'s flavor of options.
defaultParserPrefs :: Options.PrefsMod
defaultParserPrefs :: PrefsMod
defaultParserPrefs = String -> PrefsMod
Options.multiSuffix String
"..."

-- | A type family to extract fields wrapped using '(<?>)'
type family (:::) wrap wrapped
type instance Wrapped ::: wrapped = wrapped
type instance Unwrapped ::: wrapped = Unwrap wrapped

type family Unwrap ty where
  Unwrap (ty <?> helper) = Unwrap ty
  Unwrap (ty <!> defVal) = Unwrap ty
  Unwrap (ty <#> shrtNm) = Unwrap ty
  Unwrap ty = ty

infixr 0 :::

-- | Flag to keep fields wrapped
data Wrapped

-- | Flag to unwrap fields annotated using '(<?>)'
data Unwrapped
    deriving (Typeable Unwrapped
Unwrapped -> DataType
Unwrapped -> Constr
(forall b. Data b => b -> b) -> Unwrapped -> Unwrapped
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Unwrapped -> u
forall u. (forall d. Data d => d -> u) -> Unwrapped -> [u]
forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Unwrapped -> r
forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Unwrapped -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Unwrapped -> m Unwrapped
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Unwrapped -> m Unwrapped
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Unwrapped
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Unwrapped -> c Unwrapped
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Unwrapped)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Unwrapped)
gmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Unwrapped -> m Unwrapped
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Unwrapped -> m Unwrapped
gmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Unwrapped -> m Unwrapped
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Unwrapped -> m Unwrapped
gmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Unwrapped -> m Unwrapped
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Unwrapped -> m Unwrapped
gmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Unwrapped -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Unwrapped -> u
gmapQ :: forall u. (forall d. Data d => d -> u) -> Unwrapped -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Unwrapped -> [u]
gmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Unwrapped -> r
$cgmapQr :: forall r r'.
(r' -> r -> r)
-> r -> (forall d. Data d => d -> r') -> Unwrapped -> r
gmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Unwrapped -> r
$cgmapQl :: forall r r'.
(r -> r' -> r)
-> r -> (forall d. Data d => d -> r') -> Unwrapped -> r
gmapT :: (forall b. Data b => b -> b) -> Unwrapped -> Unwrapped
$cgmapT :: (forall b. Data b => b -> b) -> Unwrapped -> Unwrapped
dataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Unwrapped)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Unwrapped)
dataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Unwrapped)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Unwrapped)
dataTypeOf :: Unwrapped -> DataType
$cdataTypeOf :: Unwrapped -> DataType
toConstr :: Unwrapped -> Constr
$ctoConstr :: Unwrapped -> Constr
gunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Unwrapped
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Unwrapped
gfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Unwrapped -> c Unwrapped
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Unwrapped -> c Unwrapped
Data)

-- | Constraint for types whose fields can be unwrapped
type Unwrappable f = (Generic (f Wrapped), Generic (f Unwrapped), GenericUnwrappable (Rep (f Wrapped)) (Rep (f Unwrapped)))

class GenericUnwrappable f f' where
  genericUnwrap :: f p -> f' p

instance GenericUnwrappable U1 U1 where
  genericUnwrap :: forall p. U1 p -> U1 p
genericUnwrap = forall a. a -> a
id

instance GenericUnwrappable f f' => GenericUnwrappable (M1 i c f) (M1 i c f') where
  genericUnwrap :: forall p. M1 i c f p -> M1 i c f' p
genericUnwrap = forall k i (c :: Meta) (f :: k -> *) (p :: k). f p -> M1 i c f p
M1 forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) (f' :: * -> *) p.
GenericUnwrappable f f' =>
f p -> f' p
genericUnwrap forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall k i (c :: Meta) (f :: k -> *) (p :: k). M1 i c f p -> f p
unM1

instance (GenericUnwrappable f f', GenericUnwrappable g g') => GenericUnwrappable (f :+: g) (f' :+: g') where
  genericUnwrap :: forall p. (:+:) f g p -> (:+:) f' g' p
genericUnwrap (L1 f p
f) = forall k (f :: k -> *) (g :: k -> *) (p :: k). f p -> (:+:) f g p
L1 (forall (f :: * -> *) (f' :: * -> *) p.
GenericUnwrappable f f' =>
f p -> f' p
genericUnwrap f p
f)
  genericUnwrap (R1 g p
g) = forall k (f :: k -> *) (g :: k -> *) (p :: k). g p -> (:+:) f g p
R1 (forall (f :: * -> *) (f' :: * -> *) p.
GenericUnwrappable f f' =>
f p -> f' p
genericUnwrap g p
g)

instance (GenericUnwrappable f f', GenericUnwrappable g g') => GenericUnwrappable (f :*: g) (f' :*: g') where
  genericUnwrap :: forall p. (:*:) f g p -> (:*:) f' g' p
genericUnwrap (f p
f :*: g p
g) = forall (f :: * -> *) (f' :: * -> *) p.
GenericUnwrappable f f' =>
f p -> f' p
genericUnwrap f p
f forall k (f :: k -> *) (g :: k -> *) (p :: k).
f p -> g p -> (:*:) f g p
:*: forall (f :: * -> *) (f' :: * -> *) p.
GenericUnwrappable f f' =>
f p -> f' p
genericUnwrap g p
g

instance GenericUnwrappable (K1 i c) (K1 i c) where
  genericUnwrap :: forall p. K1 i c p -> K1 i c p
genericUnwrap = forall a. a -> a
id

instance GenericUnwrappable (K1 i field) (K1 i c)
  => GenericUnwrappable (K1 i (field <?> helper)) (K1 i c) where
    genericUnwrap :: forall p. K1 i (field <?> helper) p -> K1 i c p
genericUnwrap (K1 field <?> helper
c) = (forall (f :: * -> *) (f' :: * -> *) p.
GenericUnwrappable f f' =>
f p -> f' p
genericUnwrap :: K1 i field p -> K1 i c p) (forall k i c (p :: k). c -> K1 i c p
K1 (forall field (help :: Symbol). (field <?> help) -> field
unHelpful field <?> helper
c))

instance GenericUnwrappable (K1 i field) (K1 i c)
  => GenericUnwrappable (K1 i (field <!> defVal)) (K1 i c) where
    genericUnwrap :: forall p. K1 i (field <!> defVal) p -> K1 i c p
genericUnwrap (K1 field <!> defVal
c) = (forall (f :: * -> *) (f' :: * -> *) p.
GenericUnwrappable f f' =>
f p -> f' p
genericUnwrap :: K1 i field p -> K1 i c p) (forall k i c (p :: k). c -> K1 i c p
K1 (forall field (value :: Symbol). (field <!> value) -> field
unDefValue field <!> defVal
c))

instance GenericUnwrappable (K1 i field) (K1 i c)
  => GenericUnwrappable (K1 i (field <#> defVal)) (K1 i c) where
    genericUnwrap :: forall p. K1 i (field <#> defVal) p -> K1 i c p
genericUnwrap (K1 field <#> defVal
c) = (forall (f :: * -> *) (f' :: * -> *) p.
GenericUnwrappable f f' =>
f p -> f' p
genericUnwrap :: K1 i field p -> K1 i c p) (forall k i c (p :: k). c -> K1 i c p
K1 (forall field (value :: Symbol). (field <#> value) -> field
unShortName field <#> defVal
c))

-- | Unwrap the fields of a constructor
unwrap :: forall f . Unwrappable f => f Wrapped -> f Unwrapped
unwrap :: forall (f :: * -> *). Unwrappable f => f Wrapped -> f Unwrapped
unwrap = forall a x. Generic a => Rep a x -> a
to forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (f :: * -> *) (f' :: * -> *) p.
GenericUnwrappable f f' =>
f p -> f' p
genericUnwrap forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a x. Generic a => a -> Rep a x
from

-- | Marshal any value that implements 'ParseRecord' from the command line
-- and unwrap its fields
unwrapRecord
    :: (Functor io, MonadIO io, ParseRecord (f Wrapped), Unwrappable f)
    => Text
    -> io (f Unwrapped)
unwrapRecord :: forall (io :: * -> *) (f :: * -> *).
(Functor io, MonadIO io, ParseRecord (f Wrapped), Unwrappable f) =>
Text -> io (f Unwrapped)
unwrapRecord = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (f :: * -> *). Unwrappable f => f Wrapped -> f Unwrapped
unwrap forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (io :: * -> *) a.
(MonadIO io, ParseRecord a) =>
Text -> io a
getRecord

-- | Pure version of `unwrapRecord`
unwrapRecordPure
    :: (ParseRecord (f Wrapped), Unwrappable f)
    => [Text]
    -- ^ Command-line arguments
    -> Maybe (f Unwrapped)
unwrapRecordPure :: forall (f :: * -> *).
(ParseRecord (f Wrapped), Unwrappable f) =>
[Text] -> Maybe (f Unwrapped)
unwrapRecordPure = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall (f :: * -> *). Unwrappable f => f Wrapped -> f Unwrapped
unwrap forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ParseRecord a => [Text] -> Maybe a
getRecordPure

showHelpText :: Options.ParserPrefs -> Options.ParserInfo a -> IO ()
showHelpText :: forall a. ParserPrefs -> ParserInfo a -> IO ()
showHelpText ParserPrefs
pprefs ParserInfo a
pinfo =
  forall a. ParserResult a -> IO a
Options.handleParseResult forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a. ParserFailure ParserHelp -> ParserResult a
Options.Failure forall a b. (a -> b) -> a -> b
$
  forall a.
ParserPrefs
-> ParserInfo a
-> ParseError
-> [Context]
-> ParserFailure ParserHelp
Options.parserFailure ParserPrefs
pprefs ParserInfo a
pinfo (Maybe String -> ParseError
Options.ShowHelpText forall a. Maybe a
Nothing) forall a. Monoid a => a
mempty

-- | Marshal any value that implements 'ParseRecord' from the command line
-- and unwrap its fields alongside an io action to print the help message
unwrapWithHelp
    :: (MonadIO io, ParseRecord (f Wrapped), Unwrappable f)
    => Text
    -- ^ Program description
    -> io (f Unwrapped, io ())
    -- ^ (options, io action to print help message)
unwrapWithHelp :: forall (io :: * -> *) (f :: * -> *).
(MonadIO io, ParseRecord (f Wrapped), Unwrappable f) =>
Text -> io (f Unwrapped, io ())
unwrapWithHelp Text
desc = do
  (f Wrapped
opts, io ()
help) <- forall (io :: * -> *) a.
(MonadIO io, ParseRecord a) =>
Text -> io (a, io ())
getWithHelp Text
desc
  forall (m :: * -> *) a. Monad m => a -> m a
return (forall (f :: * -> *). Unwrappable f => f Wrapped -> f Unwrapped
unwrap f Wrapped
opts, io ()
help)