{-# LANGUAGE ConstraintKinds #-}
{-# LANGUAGE InstanceSigs #-}
{-# LANGUAGE PolyKinds #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
module Options.Harg.Operations where
import Data.Functor.Identity (Identity(..))
import qualified Data.Barbie as B
import qualified Options.Applicative as Optparse
import Options.Harg.Cmdline (mkOptparseParser)
import Options.Harg.Config (mkConfigParser, getConfig)
import Options.Harg.Het.All (All)
import Options.Harg.Het.HList (AssocListF, MapAssocList(..))
import Options.Harg.Het.Prod ((:*)(..))
import Options.Harg.Het.Variant (VariantF)
import Options.Harg.Pretty (ppOptErrors)
import Options.Harg.Sources ( accumSourceResults
, DefaultSources, defaultSources
, HiddenSources, hiddenSources
)
import Options.Harg.Sources.Types (GetSource(..), RunSource(..))
import Options.Harg.Subcommands (Subcommands(..))
import Options.Harg.Types (HargCtx(..), getCtx, Opt, OptError)
import Options.Harg.Util (toDummyOpts, allToDummyOpts, compose)
execOptWithCtx
:: forall c a.
( B.TraversableB a
, B.ProductB a
, B.TraversableB c
, B.ProductB c
, GetSource c Identity
, RunSource (SourceVal c) a
)
=> HargCtx
-> c Opt
-> a Opt
-> IO (a Identity)
execOptWithCtx ctx conf opts = do
let
configParser
= mkConfigParser ctx $ compose Identity (conf :* hiddenSources)
dummyParser
= mkOptparseParser [] (toDummyOpts @String opts)
config <- getConfig ctx configParser dummyParser
sourceVals <- getSource ctx config
let
(errs, sources)
= accumSourceResults
$ runSource sourceVals (compose Identity opts)
optParser
= mkOptparseParser sources (compose Identity opts)
allParser
= (,) <$> optParser <*> configParser
fst <$> if null errs
then execParser ctx allParser
else failParser allParser errs
execOpt
:: forall c a.
( B.TraversableB a
, B.ProductB a
, B.TraversableB c
, B.ProductB c
, GetSource c Identity
, RunSource (SourceVal c) a
)
=> c Opt
-> a Opt
-> IO (a Identity)
execOpt conf opts = do
ctx <- getCtx
execOptWithCtx ctx conf opts
execOptWithCtxDef
:: forall a.
( B.TraversableB a
, B.ProductB a
)
=> HargCtx
-> a Opt
-> IO (a Identity)
execOptWithCtxDef ctx
= execOptWithCtx ctx defaultSources
execOptDef
:: forall a.
( B.TraversableB a
, B.ProductB a
)
=> a Opt
-> IO (a Identity)
execOptDef
= execOpt defaultSources
execCommandsWithCtx
:: forall c ts xs.
( B.TraversableB (VariantF xs)
, B.TraversableB c
, B.ProductB c
, Subcommands ts xs
, GetSource c Identity
, All (RunSource (SourceVal (c :* HiddenSources))) xs
, All (RunSource ()) xs
, MapAssocList xs
)
=> HargCtx
-> c Opt
-> AssocListF ts xs Opt
-> IO (VariantF xs Identity)
execCommandsWithCtx ctx conf opts = do
let
configParser
= mkConfigParser ctx $ compose Identity (conf :* hiddenSources)
(_, dummyCommands)
= mapSubcommand () (allToDummyOpts @String opts)
dummyParser
= Optparse.subparser (mconcat dummyCommands)
config <- getConfig ctx configParser dummyParser
sourceVals <- getSource ctx config
let
(errs, commands)
= mapSubcommand sourceVals (mapAssocList (compose Identity) opts)
optParser
= Optparse.subparser (mconcat commands)
allParser
= (,) <$> optParser <*> configParser
fst <$> if null errs
then execParser ctx allParser
else failParser allParser errs
execCommands
:: forall c ts xs.
( B.TraversableB (VariantF xs)
, B.TraversableB c
, B.ProductB c
, Subcommands ts xs
, GetSource c Identity
, All (RunSource (SourceVal (c :* HiddenSources))) xs
, All (RunSource ()) xs
, MapAssocList xs
)
=> c Opt
-> AssocListF ts xs Opt
-> IO (VariantF xs Identity)
execCommands conf opts = do
ctx <- getCtx
execCommandsWithCtx ctx conf opts
execCommandsWithCtxDef
:: forall ts xs.
( B.TraversableB (VariantF xs)
, Subcommands ts xs
, All (RunSource (SourceVal (DefaultSources :* HiddenSources))) xs
, All (RunSource ()) xs
, MapAssocList xs
)
=> HargCtx
-> AssocListF ts xs Opt
-> IO (VariantF xs Identity)
execCommandsWithCtxDef ctx
= execCommandsWithCtx ctx defaultSources
execCommandsDef
:: forall ts xs.
( B.TraversableB (VariantF xs)
, Subcommands ts xs
, All (RunSource (SourceVal (DefaultSources :* HiddenSources))) xs
, All (RunSource ()) xs
, MapAssocList xs
)
=> AssocListF ts xs Opt
-> IO (VariantF xs Identity)
execCommandsDef
= execCommands defaultSources
execParser
:: HargCtx
-> Optparse.Parser a
-> IO a
execParser HargCtx{..} parser
= Optparse.handleParseResult (execParserPure _hcArgs parser)
failParser
:: Optparse.Parser a
-> [OptError]
-> IO a
failParser parser errs
= Optparse.handleParseResult (Optparse.Failure failure)
where
failure
= Optparse.parserFailure
Optparse.defaultPrefs
parserInfo
(Optparse.ErrorMsg errStr)
[]
parserInfo
= Optparse.info (Optparse.helper <*> parser) Optparse.forwardOptions
errStr
= ppOptErrors errs
execParserPure
:: [String]
-> Optparse.Parser a
-> Optparse.ParserResult a
execParserPure args parser
= let
parserInfo
= Optparse.info (Optparse.helper <*> parser) Optparse.forwardOptions
in Optparse.execParserPure Optparse.defaultPrefs parserInfo args