| Copyright | (c) OleksandrZhabenko 2021-2022 |
|---|---|
| License | MIT |
| Maintainer | olexandr543@yahoo.com |
| Stability | Experimental |
| Safe Haskell | None |
| Language | Haskell2010 |
CLI.Arguments
Description
A library to process command line arguments in some more convenient way.
Synopsis
- data Arguments
- type Args = [Arguments]
- type Specification = (Delimiter, GQtyArgs)
- type CLSpecifications = [Specification]
- type Delimiter = String
- type GQtyArgs = Int
- type FirstCharacter = Char
- type FirstChars = (Char, Char)
- isA :: Arguments -> Bool
- isB :: Arguments -> Bool
- isC :: Arguments -> Bool
- nullArguments :: Arguments -> Bool
- notNullArguments :: Arguments -> Bool
- b1Args2AArgs :: Arguments -> Arguments
- args2Args :: CLSpecifications -> [String] -> Args
- args2Args3' :: (Args, Args, Args) -> CLSpecifications -> [String] -> (Args, Args, Args)
- args2Args3 :: CLSpecifications -> [String] -> (Args, Args, Args)
- args2Args1 :: FirstChars -> CLSpecifications -> [String] -> Args
- args2Args3'1 :: FirstChars -> (Args, Args, Args) -> CLSpecifications -> [String] -> (Args, Args, Args)
- args2Args31 :: FirstChars -> CLSpecifications -> [String] -> (Args, Args, Args)
- args2ArgsFilteredG :: (Arguments -> Bool) -> CLSpecifications -> [String] -> Args
- args2ArgsFilteredG1 :: FirstChars -> (Arguments -> Bool) -> CLSpecifications -> [String] -> Args
- args2ArgsFiltered :: CLSpecifications -> [String] -> Args
- takeCs :: CLSpecifications -> [String] -> Args
- takeCs1 :: FirstChars -> CLSpecifications -> [String] -> Args
- takeBs :: CLSpecifications -> [String] -> Args
- takeAs :: CLSpecifications -> [String] -> Args
- takeArgsSortedBy :: (Arguments -> Bool) -> (Arguments -> Arguments -> Ordering) -> CLSpecifications -> [String] -> Args
- takeArgs1SortedBy :: FirstChars -> (Arguments -> Bool) -> (Arguments -> Arguments -> Ordering) -> CLSpecifications -> [String] -> Args
- takeCsSortedBy :: (Arguments -> Arguments -> Ordering) -> CLSpecifications -> [String] -> Args
- takeCs1SortedBy :: FirstChars -> (Arguments -> Arguments -> Ordering) -> CLSpecifications -> [String] -> Args
- takeBsSortedBy :: (Arguments -> Arguments -> Ordering) -> CLSpecifications -> [String] -> Args
- takeAsSortedBy :: (Arguments -> Arguments -> Ordering) -> CLSpecifications -> [String] -> Args
- takeABCsArr :: (CLSpecifications -> [String] -> Args) -> CLSpecifications -> [String] -> Array Int Arguments
- takeCsArr :: CLSpecifications -> [String] -> Array Int Arguments
- takeCs1Arr :: FirstChars -> CLSpecifications -> [String] -> Array Int Arguments
- takeBsArr :: CLSpecifications -> [String] -> Array Int Arguments
- takeAsArr :: CLSpecifications -> [String] -> Array Int Arguments
- takeABCsArrSortedBy :: ((Arguments -> Arguments -> Ordering) -> CLSpecifications -> [String] -> Args) -> (Arguments -> Arguments -> Ordering) -> CLSpecifications -> [String] -> Array Int Arguments
- takeCsArrSortedBy :: (Arguments -> Arguments -> Ordering) -> CLSpecifications -> [String] -> Array Int Arguments
- takeCs1ArrSortedBy :: FirstChars -> (Arguments -> Arguments -> Ordering) -> CLSpecifications -> [String] -> Array Int Arguments
- takeBsArrSortedBy :: (Arguments -> Arguments -> Ordering) -> CLSpecifications -> [String] -> Array Int Arguments
- takeAsArrSortedBy :: (Arguments -> Arguments -> Ordering) -> CLSpecifications -> [String] -> Array Int Arguments
- oneA :: Foldable t => String -> t Arguments -> Bool
- oneB :: Foldable t => String -> t Arguments -> Bool
- oneC :: Foldable t => String -> t Arguments -> Bool
- listA :: Foldable t => [String] -> t Arguments -> Bool
- listB :: Foldable t => [String] -> t Arguments -> Bool
- listC :: Foldable t => [String] -> t Arguments -> Bool
- getA :: Foldable t => String -> t Arguments -> String
- getB :: Foldable t => String -> t Arguments -> [String]
- getC :: Foldable t => String -> t Arguments -> [String]
- getLstA :: Foldable t => [String] -> t Arguments -> [String]
- getLstB :: Foldable t => [String] -> t Arguments -> [[String]]
- getLstC :: Foldable t => [String] -> t Arguments -> [[String]]
Documentation
Instances
type Specification = (Delimiter, GQtyArgs) Source #
type CLSpecifications = [Specification] Source #
type FirstCharacter = Char Source #
type FirstChars = (Char, Char) Source #
nullArguments :: Arguments -> Bool Source #
notNullArguments :: Arguments -> Bool Source #
b1Args2AArgs :: Arguments -> Arguments Source #
args2Args3 :: CLSpecifications -> [String] -> (Args, Args, Args) Source #
Arguments
| :: FirstChars | A pair of the first characters of the starting group delimiter (the same for all |
| -> CLSpecifications | |
| -> [String] | |
| -> Args |
Arguments
| :: FirstChars | A pair of the first characters of the starting group delimiter (the same for all |
| -> (Args, Args, Args) | |
| -> CLSpecifications | |
| -> [String] | |
| -> (Args, Args, Args) |
Arguments
| :: FirstChars | A pair of the first characters of the starting group delimiter (the same for all |
| -> CLSpecifications | |
| -> [String] | |
| -> (Args, Args, Args) |
Arguments
| :: (Arguments -> Bool) | A predicate to check which |
| -> CLSpecifications | |
| -> [String] | |
| -> Args |
This function can actually parse the command line arguments being the [String].
Arguments
| :: FirstChars | A pair of the first characters of the starting group delimiter (the same for all |
| -> (Arguments -> Bool) | A predicate to check which |
| -> CLSpecifications | |
| -> [String] | |
| -> Args |
This function can actually parse the command line arguments being the [String].
args2ArgsFiltered :: CLSpecifications -> [String] -> Args Source #
This function can actually parse the command line arguments being the [String].
Arguments
| :: FirstChars | A pair of the first characters of the starting group delimiter (the same for all |
| -> CLSpecifications | |
| -> [String] | |
| -> Args |
Arguments
| :: (Arguments -> Bool) | A predicate to check which |
| -> (Arguments -> Arguments -> Ordering) | A |
| -> CLSpecifications | |
| -> [String] | |
| -> Args |
Arguments
| :: FirstChars | A pair of the first characters of the starting group delimiter (the same for all |
| -> (Arguments -> Bool) | A predicate to check which |
| -> (Arguments -> Arguments -> Ordering) | A |
| -> CLSpecifications | |
| -> [String] | |
| -> Args |
Arguments
| :: FirstChars | A pair of the first characters of the starting group delimiter (the same for all |
| -> (Arguments -> Arguments -> Ordering) | A |
| -> CLSpecifications | |
| -> [String] | |
| -> Args |
Arguments
| :: (CLSpecifications -> [String] -> Args) | A function to collect the |
| -> CLSpecifications | |
| -> [String] | |
| -> Array Int Arguments |
For empty list of Strings returns empty array that has no elements. Trying to index it always returns error and can cause
segmentation fault in the running program or interpreter (GHCi).
takeCsArr :: CLSpecifications -> [String] -> Array Int Arguments Source #
For empty list of Strings returns empty array that has no elements. Trying to index it always returns error and can cause
segmentation fault in the running program or interpreter (GHCi).
Arguments
| :: FirstChars | A pair of the first characters of the starting group delimiter (the same for all |
| -> CLSpecifications | |
| -> [String] | |
| -> Array Int Arguments |
For empty list of Strings returns empty array that has no elements. Trying to index it always returns error and can cause
segmentation fault in the running program or interpreter (GHCi).
takeBsArr :: CLSpecifications -> [String] -> Array Int Arguments Source #
For empty list of Strings returns empty array that has no elements. Trying to index it always returns error and can cause
segmentation fault in the running program or interpreter (GHCi).
takeAsArr :: CLSpecifications -> [String] -> Array Int Arguments Source #
For empty list of Strings returns empty array that has no elements. Trying to index it always returns error and can cause
segmentation fault in the running program or interpreter (GHCi).
Arguments
| :: ((Arguments -> Arguments -> Ordering) -> CLSpecifications -> [String] -> Args) | |
| -> (Arguments -> Arguments -> Ordering) | A |
| -> CLSpecifications | |
| -> [String] | |
| -> Array Int Arguments |
For empty list of Strings returns empty array that has no elements. Trying to index it always returns error and can cause
segmentation fault in the running program or interpreter (GHCi).
Arguments
| :: (Arguments -> Arguments -> Ordering) | A |
| -> CLSpecifications | |
| -> [String] | |
| -> Array Int Arguments |
For empty list of Strings returns empty array that has no elements. Trying to index it always returns error and can cause
segmentation fault in the running program or interpreter (GHCi).
Arguments
| :: FirstChars | A pair of the first characters of the starting group delimiter (the same for all |
| -> (Arguments -> Arguments -> Ordering) | A |
| -> CLSpecifications | |
| -> [String] | |
| -> Array Int Arguments |
For empty list of Strings returns empty array that has no elements. Trying to index it always returns error and can cause
segmentation fault in the running program or interpreter (GHCi).
Arguments
| :: (Arguments -> Arguments -> Ordering) | A |
| -> CLSpecifications | |
| -> [String] | |
| -> Array Int Arguments |
For empty list of Strings returns empty array that has no elements. Trying to index it always returns error and can cause
segmentation fault in the running program or interpreter (GHCi).
Arguments
| :: (Arguments -> Arguments -> Ordering) | A |
| -> CLSpecifications | |
| -> [String] | |
| -> Array Int Arguments |
For empty list of Strings returns empty array that has no elements. Trying to index it always returns error and can cause
segmentation fault in the running program or interpreter (GHCi).