cifl-math-library-1.1.1.0: Math libraries
Safe HaskellSafe-Inferred
LanguageHaskell2010

Math.Tools.Cmdline

Documentation

data ParseExceptions Source #

Instances

Instances details
Data ParseExceptions Source # 
Instance details

Defined in Math.Tools.Cmdline

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ParseExceptions -> c ParseExceptions #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ParseExceptions #

toConstr :: ParseExceptions -> Constr #

dataTypeOf :: ParseExceptions -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c ParseExceptions) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ParseExceptions) #

gmapT :: (forall b. Data b => b -> b) -> ParseExceptions -> ParseExceptions #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ParseExceptions -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ParseExceptions -> r #

gmapQ :: (forall d. Data d => d -> u) -> ParseExceptions -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ParseExceptions -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ParseExceptions -> m ParseExceptions #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ParseExceptions -> m ParseExceptions #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ParseExceptions -> m ParseExceptions #

Exception ParseExceptions Source # 
Instance details

Defined in Math.Tools.Cmdline

Generic ParseExceptions Source # 
Instance details

Defined in Math.Tools.Cmdline

Associated Types

type Rep ParseExceptions :: Type -> Type #

Show ParseExceptions Source # 
Instance details

Defined in Math.Tools.Cmdline

type Rep ParseExceptions Source # 
Instance details

Defined in Math.Tools.Cmdline

type Rep ParseExceptions = D1 ('MetaData "ParseExceptions" "Math.Tools.Cmdline" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'False) (C1 ('MetaCons "CannotParseException" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :+: (C1 ('MetaCons "IncompleteParseException" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text) :*: S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "AmbiguousParseException" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 [(Text, Text)]))))

data CmdlineParsingMT m a Source #

Constructors

CmdlineParsingMT 

Fields

Instances

Instances details
MonadIO m => MonadIO (CmdlineParsingMT m) Source # 
Instance details

Defined in Math.Tools.Cmdline

Methods

liftIO :: IO a -> CmdlineParsingMT m a #

Alternative m => Alternative (CmdlineParsingMT m) Source # 
Instance details

Defined in Math.Tools.Cmdline

Applicative m => Applicative (CmdlineParsingMT m) Source # 
Instance details

Defined in Math.Tools.Cmdline

Functor m => Functor (CmdlineParsingMT m) Source # 
Instance details

Defined in Math.Tools.Cmdline

Methods

fmap :: (a -> b) -> CmdlineParsingMT m a -> CmdlineParsingMT m b #

(<$) :: a -> CmdlineParsingMT m b -> CmdlineParsingMT m a #

Monad m => Monad (CmdlineParsingMT m) Source # 
Instance details

Defined in Math.Tools.Cmdline

data LookupExceptions Source #

Constructors

NotFoundException !Text 

Instances

Instances details
Data LookupExceptions Source # 
Instance details

Defined in Math.Tools.Cmdline

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> LookupExceptions -> c LookupExceptions #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c LookupExceptions #

toConstr :: LookupExceptions -> Constr #

dataTypeOf :: LookupExceptions -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c LookupExceptions) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c LookupExceptions) #

gmapT :: (forall b. Data b => b -> b) -> LookupExceptions -> LookupExceptions #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> LookupExceptions -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> LookupExceptions -> r #

gmapQ :: (forall d. Data d => d -> u) -> LookupExceptions -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> LookupExceptions -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> LookupExceptions -> m LookupExceptions #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> LookupExceptions -> m LookupExceptions #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> LookupExceptions -> m LookupExceptions #

Exception LookupExceptions Source # 
Instance details

Defined in Math.Tools.Cmdline

Generic LookupExceptions Source # 
Instance details

Defined in Math.Tools.Cmdline

Associated Types

type Rep LookupExceptions :: Type -> Type #

Show LookupExceptions Source # 
Instance details

Defined in Math.Tools.Cmdline

type Rep LookupExceptions Source # 
Instance details

Defined in Math.Tools.Cmdline

type Rep LookupExceptions = D1 ('MetaData "LookupExceptions" "Math.Tools.Cmdline" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'False) (C1 ('MetaCons "NotFoundException" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))

lookupOption :: (ExceptionalMonad m, Read a, Show a) => Text -> CmdlineParsingMT m a Source #

lookupOptionText :: ExceptionalMonad m => Text -> CmdlineParsingMT m Text Source #

readOption :: (Read b, Show b) => Map Text Text -> Text -> IO b Source #

readerParse :: (Show a, Read a, ExceptionalMonad m) => Text -> m a Source #

data CommandLineException Source #

Instances

Instances details
Data CommandLineException Source # 
Instance details

Defined in Math.Tools.Cmdline

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CommandLineException -> c CommandLineException #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CommandLineException #

toConstr :: CommandLineException -> Constr #

dataTypeOf :: CommandLineException -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CommandLineException) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CommandLineException) #

gmapT :: (forall b. Data b => b -> b) -> CommandLineException -> CommandLineException #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CommandLineException -> r #

gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CommandLineException -> r #

gmapQ :: (forall d. Data d => d -> u) -> CommandLineException -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CommandLineException -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CommandLineException -> m CommandLineException #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CommandLineException -> m CommandLineException #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CommandLineException -> m CommandLineException #

Exception CommandLineException Source # 
Instance details

Defined in Math.Tools.Cmdline

Generic CommandLineException Source # 
Instance details

Defined in Math.Tools.Cmdline

Associated Types

type Rep CommandLineException :: Type -> Type #

Show CommandLineException Source # 
Instance details

Defined in Math.Tools.Cmdline

type Rep CommandLineException Source # 
Instance details

Defined in Math.Tools.Cmdline

type Rep CommandLineException = D1 ('MetaData "CommandLineException" "Math.Tools.Cmdline" "cifl-math-library-1.1.1.0-JEQP78tsA0rJRaFkv5LJVZ" 'False) (C1 ('MetaCons "MissingCommandLineArgument" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)) :+: C1 ('MetaCons "InvalidCommandLineArgument" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'SourceStrict 'DecidedStrict) (Rec0 Text)))

splitArgs :: ExceptionalMonad m => [Text] -> Map Text Text -> m (Map Text Text) Source #

withOptions :: Map Text Text -> ((?cmdlineoptions :: Map Text Text) => IO a) -> IO a Source #

findOption :: (?cmdlineoptions :: Map Text Text, Read b, Show b) => Text -> IO b Source #