module Options.Generic (
getRecord
, getWithHelp
, getRecordPure
, unwrapRecord
, unwrapWithHelp
, unwrapRecordPure
, ParseRecord(..)
, ParseFields(..)
, ParseField(..)
, Only(..)
, getOnly
, Modifiers(..)
, parseRecordWithModifiers
, defaultModifiers
, lispCaseModifiers
, firstLetter
, type (<?>)(..)
, type (:::)
, Wrapped
, Unwrapped
, Unwrappable
, Generic
, Text
, All(..)
, Any(..)
, First(..)
, Last(..)
, Sum(..)
, Product(..)
) where
import Control.Applicative
import Control.Monad.IO.Class (MonadIO(..))
import Data.Char (isUpper, toLower, toUpper)
import Data.Int (Int8, Int16, Int32, Int64)
import Data.Monoid
import Data.List.NonEmpty (NonEmpty((:|)))
import Data.Proxy
import Data.Text (Text)
import Data.Tuple.Only (Only(..))
import Data.Typeable (Typeable)
import Data.Void (Void)
import Data.Word (Word8, Word16, Word32, Word64)
import Data.Foldable (foldMap)
import Filesystem.Path (FilePath)
import GHC.Generics
import Prelude hiding (FilePath)
import Options.Applicative (Parser, ReadM)
import qualified Data.Text
import qualified Data.Text.Encoding
import qualified Data.Text.Lazy
import qualified Data.Text.Lazy.Encoding
import qualified Data.Time.Calendar
import qualified Data.Time.Format
import qualified Data.Typeable
import qualified Data.ByteString
import qualified Data.ByteString.Lazy
import qualified Filesystem.Path.CurrentOS as Filesystem
import qualified Options.Applicative as Options
import qualified Options.Applicative.Types as Options
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
auto :: Read a => ReadM a
auto = do
s <- Options.readerAsk
case Text.Read.readMaybe s of
Just x -> return x
Nothing -> Options.readerAbort Options.ShowHelpText
class ParseField a where
parseField
:: Maybe Text
-> Maybe Text
-> Maybe Char
-> Parser a
default parseField
:: (Typeable a, Read a)
=> Maybe Text
-> Maybe Text
-> Maybe Char
-> Parser a
parseField h m c = do
let metavar = map toUpper (show (Data.Typeable.typeOf (undefined :: a)))
case m of
Nothing -> do
let fs = Options.metavar metavar
<> foldMap (Options.help . Data.Text.unpack) h
Options.argument readField fs
Just name -> do
let fs = Options.metavar metavar
<> Options.long (Data.Text.unpack name)
<> foldMap (Options.help . Data.Text.unpack) h
<> foldMap Options.short c
Options.option readField fs
parseListOfField
:: Maybe Text
-> Maybe Text
-> Maybe Char
-> Parser [a]
parseListOfField h m c = many (parseField h m c)
readField :: ReadM a
default readField :: Read a => ReadM a
readField = auto
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) => ReadM a
readIntegralBounded =
auto >>= f
where
f i | i < lower = fail msg
| i > upper = fail msg
| otherwise = pure $ fromInteger i
lower = toInteger (minBound :: a)
upper = toInteger (maxBound :: a)
msg = map toUpper (show (Data.Typeable.typeOf (undefined :: a))) <>
" must be within the range [" <>
show lower <> " .. " <> show upper <> "]"
instance ParseField Int where readField = readIntegralBounded
instance ParseField Int8 where readField = readIntegralBounded
instance ParseField Int16 where readField = readIntegralBounded
instance ParseField Int32 where readField = readIntegralBounded
instance ParseField Int64 where readField = readIntegralBounded
instance ParseField Word8 where readField = readIntegralBounded
instance ParseField Word16 where readField = readIntegralBounded
instance ParseField Word32 where readField = readIntegralBounded
instance ParseField Word64 where readField = readIntegralBounded
#if MIN_VERSION_base(4,8,0)
instance ParseField Natural where
readField =
auto >>= f
where
f i | i < 0 = fail msg
| otherwise = pure $ fromInteger i
msg = "NATURAL cannot be negative"
#endif
instance ParseField String where
parseField = parseHelpfulString "STRING"
instance ParseField Char where
parseField h m c = do
let metavar = "CHAR"
let readM = do
s <- Options.readerAsk
case s of
[ch] -> return ch
_ -> Options.readerAbort Options.ShowHelpText
case m of
Nothing -> do
let fs = Options.metavar metavar
<> foldMap (Options.help . Data.Text.unpack) h
Options.argument readM fs
Just name -> do
let fs = Options.metavar metavar
<> Options.long (Data.Text.unpack name)
<> foldMap (Options.help . Data.Text.unpack) h
<> foldMap Options.short c
Options.option readM fs
parseListOfField = parseHelpfulString "STRING"
instance ParseField Any where
parseField h m c = Any <$> parseField h m c
instance ParseField All where
parseField h m c = All <$> parseField h m c
parseHelpfulString
:: String -> Maybe Text -> Maybe Text -> Maybe Char -> Parser String
parseHelpfulString metavar h m c =
case m of
Nothing -> do
let fs = Options.metavar metavar
<> foldMap (Options.help . Data.Text.unpack) h
Options.argument Options.str fs
Just name -> do
let fs = Options.metavar metavar
<> Options.long (Data.Text.unpack name)
<> foldMap (Options.help . Data.Text.unpack) h
<> foldMap Options.short c
Options.option Options.str fs
instance ParseField Data.Text.Text where
parseField h m c = Data.Text.pack <$> parseHelpfulString "TEXT" h m c
instance ParseField Data.ByteString.ByteString where
parseField h m c = fmap Data.Text.Encoding.encodeUtf8 (parseField h m c)
instance ParseField Data.Text.Lazy.Text where
parseField h m c = Data.Text.Lazy.pack <$> parseHelpfulString "TEXT" h m c
instance ParseField Data.ByteString.Lazy.ByteString where
parseField h m c = fmap Data.Text.Lazy.Encoding.encodeUtf8 (parseField h m c)
instance ParseField FilePath where
parseField h m c = Filesystem.decodeString <$> parseHelpfulString "FILEPATH" h m c
readField = Options.str
instance ParseField Data.Time.Calendar.Day where
parseField h m c = do
let metavar = "YYYY-MM-DD"
case m of
Nothing -> do
let fs = Options.metavar metavar
<> foldMap (Options.help . Data.Text.unpack) h
Options.argument iso8601Day fs
Just name -> do
let fs = Options.metavar metavar
<> Options.long (Data.Text.unpack name)
<> foldMap (Options.help . Data.Text.unpack) h
<> foldMap Options.short c
Options.option iso8601Day fs
where
iso8601Day = Options.eitherReader
$ runReadS . Data.Time.Format.readSTime
False
Data.Time.Format.defaultTimeLocale
"%F"
runReadS [(day, "")] = Right day
runReadS _ = Left "expected YYYY-MM-DD"
class ParseRecord a => ParseFields a where
parseFields
:: Maybe Text
-> Maybe Text
-> Maybe Char
-> Parser a
default parseFields
:: ParseField a => Maybe Text -> Maybe Text -> Maybe Char -> Parser a
parseFields = 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 FilePath
instance ParseFields Data.Time.Calendar.Day
#if MIN_VERSION_base(4,8,0)
instance ParseFields Natural
#endif
instance ParseFields Bool where
parseFields h m c =
case m of
Nothing -> do
let fs = Options.metavar "BOOL"
<> foldMap (Options.help . Data.Text.unpack) h
Options.argument auto fs
Just name -> do
Options.switch $
Options.long (Data.Text.unpack name)
<> foldMap (Options.help . Data.Text.unpack) h
<> foldMap Options.short c
instance ParseFields () where
parseFields _ _ _ = pure ()
instance ParseFields Any where
parseFields h m c = (fmap mconcat . many . fmap Any) (parseField h m c)
instance ParseFields All where
parseFields h m c = (fmap mconcat . many . fmap All) (parseField h m c)
instance ParseField a => ParseFields (Maybe a) where
parseFields h m c = optional (parseField h m c)
instance ParseField a => ParseFields (First a) where
parseFields h m c = (fmap mconcat . many . fmap (First . Just)) (parseField h m c)
instance ParseField a => ParseFields (Last a) where
parseFields h m c = (fmap mconcat . many . fmap (Last . Just)) (parseField h m c)
instance (Num a, ParseField a) => ParseFields (Sum a) where
parseFields h m c = (fmap mconcat . many . fmap Sum) (parseField h m c)
instance (Num a, ParseField a) => ParseFields (Product a) where
parseFields h m c = (fmap mconcat . many . fmap Product) (parseField h m c)
instance ParseField a => ParseFields [a] where
parseFields = parseListOfField
instance ParseField a => ParseFields (NonEmpty a) where
parseFields h m c = (:|) <$> parseField h m c <*> parseListOfField h m c
newtype (<?>) (field :: *) (help :: Symbol) = Helpful { unHelpful :: field } deriving (Generic, Show)
instance (ParseField a, KnownSymbol h) => ParseField (a <?> h) where
parseField _ m c = Helpful <$>
parseField ((Just . Data.Text.pack .symbolVal) (Proxy :: Proxy h)) m c
readField = Helpful <$> readField
instance (ParseFields a, KnownSymbol h) => ParseFields (a <?> h) where
parseFields _ m c = Helpful <$>
parseFields ((Just . Data.Text.pack .symbolVal) (Proxy :: Proxy h)) m c
instance (ParseFields a, KnownSymbol h) => ParseRecord (a <?> h)
newtype Only_ a = Only_ a deriving (Generic, Show)
getOnly :: Only a -> a
getOnly (Only x) = x
class ParseRecord a where
parseRecord :: Parser a
default parseRecord :: (Generic a, GenericParseRecord (Rep a)) => Parser a
parseRecord = fmap GHC.Generics.to (genericParseRecord defaultModifiers)
instance ParseFields a => ParseRecord (Only_ a)
instance ParseFields a => ParseRecord (Only a) where
parseRecord = fmap adapt parseRecord
where
adapt (Only_ x) = Only x
instance ParseRecord Char where
parseRecord = fmap getOnly parseRecord
instance ParseRecord Double where
parseRecord = fmap getOnly parseRecord
instance ParseRecord Float where
parseRecord = fmap getOnly parseRecord
instance ParseRecord Int where
parseRecord = fmap getOnly parseRecord
instance ParseRecord Int8 where
parseRecord = fmap getOnly parseRecord
instance ParseRecord Int16 where
parseRecord = fmap getOnly parseRecord
instance ParseRecord Int32 where
parseRecord = fmap getOnly parseRecord
instance ParseRecord Int64 where
parseRecord = fmap getOnly parseRecord
instance ParseRecord Ordering
instance ParseRecord Void
instance ParseRecord Word8 where
parseRecord = fmap getOnly parseRecord
instance ParseRecord Word16 where
parseRecord = fmap getOnly parseRecord
instance ParseRecord Word32 where
parseRecord = fmap getOnly parseRecord
instance ParseRecord Word64 where
parseRecord = fmap getOnly parseRecord
instance ParseRecord ()
#if MIN_VERSION_base(4,8,0)
instance ParseRecord Natural where
parseRecord = fmap getOnly parseRecord
#endif
instance ParseRecord Bool where
parseRecord = fmap getOnly parseRecord
instance ParseRecord Integer where
parseRecord = fmap getOnly parseRecord
instance ParseRecord Data.Text.Text where
parseRecord = fmap getOnly parseRecord
instance ParseRecord Data.Text.Lazy.Text where
parseRecord = fmap getOnly parseRecord
instance ParseRecord Any where
parseRecord = fmap getOnly parseRecord
instance ParseRecord All where
parseRecord = fmap getOnly parseRecord
instance ParseRecord FilePath where
parseRecord = fmap getOnly parseRecord
instance ParseRecord Data.ByteString.ByteString where
parseRecord = fmap getOnly parseRecord
instance ParseRecord Data.ByteString.Lazy.ByteString where
parseRecord = fmap getOnly parseRecord
instance ParseRecord Data.Time.Calendar.Day where
parseRecord = fmap getOnly parseRecord
instance ParseField a => ParseRecord (Maybe a) where
parseRecord = fmap getOnly parseRecord
instance ParseField a => ParseRecord (First a) where
parseRecord = fmap getOnly parseRecord
instance ParseField a => ParseRecord (Last a) where
parseRecord = fmap getOnly parseRecord
instance (Num a, ParseField a) => ParseRecord (Sum a) where
parseRecord = fmap getOnly parseRecord
instance (Num a, ParseField a) => ParseRecord (Product a) where
parseRecord = fmap getOnly parseRecord
instance ParseField a => ParseRecord [a] where
parseRecord = fmap getOnly parseRecord
instance ParseField a => ParseRecord (NonEmpty a) where
parseRecord = fmap getOnly 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)
data Modifiers = Modifiers
{ fieldNameModifier :: String -> String
, constructorNameModifier :: String -> String
, shortNameModifier :: String -> Maybe Char
}
defaultModifiers :: Modifiers
defaultModifiers = Modifiers
{ fieldNameModifier = id
, constructorNameModifier = map toLower
, shortNameModifier = \_ -> Nothing
}
lispCaseModifiers :: Modifiers
lispCaseModifiers = Modifiers lispCase lispCase (\_ -> Nothing)
where
lispCase = dropWhile (== '-') . (>>= lower) . dropWhile (== '_')
lower c | isUpper c = ['-', toLower c]
| otherwise = [c]
firstLetter :: String -> Maybe Char
firstLetter (c:_) = Just c
firstLetter _ = Nothing
class GenericParseRecord f where
genericParseRecord :: Modifiers -> Parser (f p)
instance GenericParseRecord U1 where
genericParseRecord _ = pure U1
instance GenericParseRecord f => GenericParseRecord (M1 C c f) where
genericParseRecord = fmap M1 . genericParseRecord
instance (GenericParseRecord (f :+: g), GenericParseRecord (h :+: i)) => GenericParseRecord ((f :+: g) :+: (h :+: i)) where
genericParseRecord mods = do
fmap L1 (genericParseRecord mods) <|> fmap R1 (genericParseRecord mods)
instance (Constructor c, GenericParseRecord f, GenericParseRecord (g :+: h)) => GenericParseRecord (M1 C c f :+: (g :+: h)) where
genericParseRecord mods@Modifiers{..} = do
let m :: M1 i c f a
m = undefined
let name = constructorNameModifier (conName m)
let info = Options.info (Options.helper <*> (genericParseRecord mods)) mempty
let subparserFields =
Options.command name info
<> Options.metavar name
let parser = Options.subparser subparserFields
fmap (L1 . M1) parser <|> fmap R1 (genericParseRecord mods)
instance (Constructor c, GenericParseRecord (f :+: g), GenericParseRecord h) => GenericParseRecord ((f :+: g) :+: M1 C c h) where
genericParseRecord mods@Modifiers{..} = do
let m :: M1 i c h a
m = undefined
let name = constructorNameModifier (conName m)
let info = Options.info (Options.helper <*> (genericParseRecord mods)) mempty
let subparserFields =
Options.command name info
<> Options.metavar name
let parser = Options.subparser subparserFields
fmap L1 (genericParseRecord mods) <|> fmap (R1 . M1) parser
instance (Constructor c1, Constructor c2, GenericParseRecord f1, GenericParseRecord f2) => GenericParseRecord (M1 C c1 f1 :+: M1 C c2 f2) where
genericParseRecord mods@Modifiers{..} = do
let m1 :: M1 i c1 f a
m1 = undefined
let m2 :: M1 i c2 g a
m2 = undefined
let name1 = constructorNameModifier (conName m1)
let name2 = constructorNameModifier (conName m2)
let info1 = Options.info (Options.helper <*> (genericParseRecord mods)) mempty
let info2 = Options.info (Options.helper <*> (genericParseRecord mods)) mempty
let subparserFields1 =
Options.command name1 info1
<> Options.metavar name1
let subparserFields2 =
Options.command name2 info2
<> Options.metavar name2
let parser1 = Options.subparser subparserFields1
let parser2 = Options.subparser subparserFields2
fmap (L1 . M1) parser1 <|> fmap (R1 . M1) parser2
instance (GenericParseRecord f, GenericParseRecord g) => GenericParseRecord (f :*: g) where
genericParseRecord mods = liftA2 (:*:) (genericParseRecord mods) (genericParseRecord mods)
instance GenericParseRecord V1 where
genericParseRecord _ = empty
instance (Selector s, ParseFields a) => GenericParseRecord (M1 S s (K1 i a)) where
genericParseRecord Modifiers{..} = do
let m :: M1 i s f a
m = undefined
let label = case selName m of
"" -> Nothing
name -> Just (Data.Text.pack (fieldNameModifier name))
let shortName = shortNameModifier (selName m)
fmap (M1 . K1) (parseFields Nothing label shortName)
instance GenericParseRecord f => GenericParseRecord (M1 D c f) where
genericParseRecord mods = fmap M1 (Options.helper <*> genericParseRecord mods)
parseRecordWithModifiers
:: (Generic a, GenericParseRecord (Rep a)) => Modifiers -> Parser a
parseRecordWithModifiers mods = fmap GHC.Generics.to (genericParseRecord mods)
getRecord
:: (MonadIO io, ParseRecord a)
=> Text
-> io a
getRecord desc = getRecordWith header mempty
where
header = Options.header (Data.Text.unpack desc)
getRecordWith
:: (MonadIO io, ParseRecord a)
=> Options.InfoMod a
-> Options.PrefsMod
-> io a
getRecordWith infoMods prefsMods = liftIO (Options.customExecParser prefs info)
where
prefs = Options.prefs (defaultParserPrefs <> prefsMods)
info = Options.info parseRecord infoMods
getWithHelp
:: (MonadIO io, ParseRecord a)
=> Text
-> io (a, io ())
getWithHelp desc = do
a <- getRecordWith header mempty
return (a, help)
where
header = Options.header (Data.Text.unpack desc)
info = Options.info parseRecord header
help = liftIO (showHelpText (Options.prefs defaultParserPrefs) info)
getRecordPure
:: ParseRecord a
=> [Text]
-> Maybe a
getRecordPure args = getRecordPureWith args mempty mempty
getRecordPureWith
:: ParseRecord a
=> [Text]
-> Options.InfoMod a
-> Options.PrefsMod
-> Maybe a
getRecordPureWith args infoMod prefsMod = do
let header = Options.header ""
let info = Options.info parseRecord (header <> infoMod)
let prefs = Options.prefs (defaultParserPrefs <> prefsMod)
let args' = map Data.Text.unpack args
Options.getParseResult (Options.execParserPure prefs info args')
defaultParserPrefs :: Options.PrefsMod
defaultParserPrefs = Options.multiSuffix "..."
type family (:::) wrap wrapped
type instance Wrapped ::: wrapped = wrapped
type instance Unwrapped ::: (field <?> helper) = field
infixr 0 :::
data Wrapped
data 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 = id
instance GenericUnwrappable f f' => GenericUnwrappable (M1 i c f) (M1 i c f') where
genericUnwrap = M1 . genericUnwrap . unM1
instance (GenericUnwrappable f f', GenericUnwrappable g g') => GenericUnwrappable (f :+: g) (f' :+: g') where
genericUnwrap (L1 f) = L1 (genericUnwrap f)
genericUnwrap (R1 g) = R1 (genericUnwrap g)
instance (GenericUnwrappable f f', GenericUnwrappable g g') => GenericUnwrappable (f :*: g) (f' :*: g') where
genericUnwrap (f :*: g) = genericUnwrap f :*: genericUnwrap g
instance GenericUnwrappable (K1 i c) (K1 i c) where
genericUnwrap = id
instance GenericUnwrappable (K1 i (field <?> helper)) (K1 i field) where
genericUnwrap (K1 c) = K1 (unHelpful c)
unwrap :: forall f . Unwrappable f => f Wrapped -> f Unwrapped
unwrap = to . genericUnwrap . from
unwrapRecord
:: (Functor io, MonadIO io, ParseRecord (f Wrapped), Unwrappable f)
=> Text
-> io (f Unwrapped)
unwrapRecord = fmap unwrap . getRecord
unwrapRecordPure
:: (ParseRecord (f Wrapped), Unwrappable f)
=> [Text]
-> Maybe (f Unwrapped)
unwrapRecordPure = fmap unwrap . getRecordPure
showHelpText :: Options.ParserPrefs -> Options.ParserInfo a -> IO ()
showHelpText pprefs pinfo =
Options.handleParseResult . Options.Failure $
Options.parserFailure pprefs pinfo Options.ShowHelpText mempty
unwrapWithHelp
:: (MonadIO io, ParseRecord (f Wrapped), Unwrappable f)
=> Text
-> io (f Unwrapped, io ())
unwrapWithHelp desc = do
(opts, help) <- getWithHelp desc
return (unwrap opts, help)