{-# OPTIONS_HADDOCK show-extensions #-}
{-# LANGUAGE NoImplicitPrelude #-}

-- |
-- Module      :  CLI.Arguments.Arr
-- Copyright   :  (c) OleksandrZhabenko 2021-2023
-- License     :  MIT
-- Stability   :  Experimental
-- Maintainer  :  oleksandr.zhabenko@yahoo.com
--
-- A library to process command line arguments in some more convenient way.

module CLI.Arguments.Arr where

import GHC.Base
import Data.Tuple
import GHC.Arr
import GHC.List (length)
import GHC.Num ((-))
import CLI.Arguments
import CLI.Arguments.Parsing
import CLI.Arguments.Sorted

-- | For empty list of 'String's 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).
takeABCsArr
  :: (CLSpecifications -> [String] -> Args) -- ^ A function to collect the 'Args'
  -> CLSpecifications
  -> [String]
  -> Array Int Arguments
takeABCsArr :: (CLSpecifications -> [String] -> Args)
-> CLSpecifications -> [String] -> Array Int Arguments
takeABCsArr CLSpecifications -> [String] -> Args
f CLSpecifications
ts [String]
xss = forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0,Int
lforall a. Num a => a -> a -> a
-Int
1) Args
js
     where js :: Args
js = CLSpecifications -> [String] -> Args
f CLSpecifications
ts [String]
xss
           l :: Int
l = forall a. [a] -> Int
length Args
js
{-# INLINABLE takeABCsArr #-}

-- | For empty list of 'String's 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
takeCsArr :: CLSpecifications -> [String] -> Array Int Arguments
takeCsArr = (CLSpecifications -> [String] -> Args)
-> CLSpecifications -> [String] -> Array Int Arguments
takeABCsArr (\CLSpecifications
us [String]
zss -> forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. CLSpecifications -> [String] -> (Args, [String])
takeCsR CLSpecifications
us forall a b. (a -> b) -> a -> b
$ [String]
zss)
{-# INLINABLE takeCsArr #-}

-- | For empty list of 'String's 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).
takeCs1Arr
  :: FirstChars -- ^ A pair of the first characters of the starting group delimiter (the same for all 'String's in the all 'CLSpecifications') and the probable its modification (the first character of the last delimiter).
  -> CLSpecifications
  -> [String]
  -> Array Int Arguments
takeCs1Arr :: FirstChars -> CLSpecifications -> [String] -> Array Int Arguments
takeCs1Arr (Char
x1,Char
x2) = (CLSpecifications -> [String] -> Args)
-> CLSpecifications -> [String] -> Array Int Arguments
takeABCsArr (\CLSpecifications
us [String]
zss -> forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. FirstChars -> CLSpecifications -> [String] -> (Args, [String])
takeCs1R (Char
x1,Char
x2) CLSpecifications
us forall a b. (a -> b) -> a -> b
$ [String]
zss)
{-# INLINABLE takeCs1Arr #-}

-- | For empty list of 'String's 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
takeBsArr :: CLSpecifications -> [String] -> Array Int Arguments
takeBsArr = (CLSpecifications -> [String] -> Args)
-> CLSpecifications -> [String] -> Array Int Arguments
takeABCsArr (\CLSpecifications
us [String]
zss -> forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. CLSpecifications -> [String] -> (Args, [String])
takeBsR CLSpecifications
us forall a b. (a -> b) -> a -> b
$ [String]
zss)
{-# INLINABLE takeBsArr #-}

-- | For empty list of 'String's 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
takeAsArr :: CLSpecifications -> [String] -> Array Int Arguments
takeAsArr  = (CLSpecifications -> [String] -> Args)
-> CLSpecifications -> [String] -> Array Int Arguments
takeABCsArr (\CLSpecifications
us [String]
zss -> forall a b. (a, b) -> a
fst forall b c a. (b -> c) -> (a -> b) -> a -> c
. CLSpecifications -> [String] -> (Args, [String])
takeAsR CLSpecifications
us forall a b. (a -> b) -> a -> b
$ [String]
zss)
{-# INLINABLE takeAsArr #-}

---------------------------------------------------

-- | For empty list of 'String's 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).
takeABCsArrSortedBy
  :: ((Arguments -> Arguments -> Ordering) -> CLSpecifications -> [String] -> Args)
  -> (Arguments -> Arguments -> Ordering) -- ^ A 'compare'-like implementation for 'Arguments'. If needed you can implement your own 'Ord' instance for 'Arguments' and use it here. Here can be partial, just for 'C's.
  -> CLSpecifications
  -> [String]
  -> Array Int Arguments
takeABCsArrSortedBy :: ((Arguments -> Arguments -> Ordering)
 -> CLSpecifications -> [String] -> Args)
-> (Arguments -> Arguments -> Ordering)
-> CLSpecifications
-> [String]
-> Array Int Arguments
takeABCsArrSortedBy (Arguments -> Arguments -> Ordering)
-> CLSpecifications -> [String] -> Args
g Arguments -> Arguments -> Ordering
f CLSpecifications
ts [String]
xss = forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0,Int
lforall a. Num a => a -> a -> a
-Int
1) Args
js
     where js :: Args
js = (Arguments -> Arguments -> Ordering)
-> CLSpecifications -> [String] -> Args
g Arguments -> Arguments -> Ordering
f  CLSpecifications
ts [String]
xss
           l :: Int
l = forall a. [a] -> Int
length Args
js
{-# INLINABLE takeABCsArrSortedBy #-}

-- | For empty list of 'String's 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).
takeCsArrSortedBy
  :: (Arguments -> Arguments -> Ordering) -- ^ A 'compare'-like implementation for 'Arguments'. If needed you can implement your own 'Ord' instance for 'Arguments' and use it here. Here can be partial, just for 'C's.
  -> CLSpecifications
  -> [String]
  -> Array Int Arguments
takeCsArrSortedBy :: (Arguments -> Arguments -> Ordering)
-> CLSpecifications -> [String] -> Array Int Arguments
takeCsArrSortedBy = ((Arguments -> Arguments -> Ordering)
 -> CLSpecifications -> [String] -> Args)
-> (Arguments -> Arguments -> Ordering)
-> CLSpecifications
-> [String]
-> Array Int Arguments
takeABCsArrSortedBy ((Arguments -> Bool)
-> (Arguments -> Arguments -> Ordering)
-> CLSpecifications
-> [String]
-> Args
takeArgsSortedBy (\Arguments
x -> Arguments -> Bool
notNullArguments Arguments
x Bool -> Bool -> Bool
&& Arguments -> Bool
isC Arguments
x))
{-# INLINABLE takeCsArrSortedBy #-}

-- | For empty list of 'String's 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).
takeCs1ArrSortedBy
  :: FirstChars -- ^ A pair of the first characters of the starting group delimiter (the same for all 'String's in the all 'CLSpecifications') and the probable its modification being also the first character.
  -> (Arguments -> Arguments -> Ordering) -- ^ A 'compare'-like implementation for 'Arguments'. If needed you can implement your own 'Ord' instance for 'Arguments' and use it here. Here can be partial, just for 'C's.
  -> CLSpecifications
  -> [String]
  -> Array Int Arguments
takeCs1ArrSortedBy :: FirstChars
-> (Arguments -> Arguments -> Ordering)
-> CLSpecifications
-> [String]
-> Array Int Arguments
takeCs1ArrSortedBy (Char
x1,Char
x2) = ((Arguments -> Arguments -> Ordering)
 -> CLSpecifications -> [String] -> Args)
-> (Arguments -> Arguments -> Ordering)
-> CLSpecifications
-> [String]
-> Array Int Arguments
takeABCsArrSortedBy (FirstChars
-> (Arguments -> Bool)
-> (Arguments -> Arguments -> Ordering)
-> CLSpecifications
-> [String]
-> Args
takeArgs1SortedBy (Char
x1,Char
x2) (\Arguments
x -> Arguments -> Bool
notNullArguments Arguments
x Bool -> Bool -> Bool
&& Arguments -> Bool
isC Arguments
x))
{-# INLINABLE takeCs1ArrSortedBy #-}

-- | For empty list of 'String's 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).
takeBsArrSortedBy
  :: (Arguments -> Arguments -> Ordering) -- ^ A 'compare'-like implementation for 'Arguments'. If needed you can implement your own 'Ord' instance for 'Arguments' and use it here. Here can be partial, just for 'B's.
  -> CLSpecifications
  -> [String]
  -> Array Int Arguments
takeBsArrSortedBy :: (Arguments -> Arguments -> Ordering)
-> CLSpecifications -> [String] -> Array Int Arguments
takeBsArrSortedBy = ((Arguments -> Arguments -> Ordering)
 -> CLSpecifications -> [String] -> Args)
-> (Arguments -> Arguments -> Ordering)
-> CLSpecifications
-> [String]
-> Array Int Arguments
takeABCsArrSortedBy ((Arguments -> Bool)
-> (Arguments -> Arguments -> Ordering)
-> CLSpecifications
-> [String]
-> Args
takeArgsSortedBy (\Arguments
x -> Arguments -> Bool
notNullArguments Arguments
x Bool -> Bool -> Bool
&& Arguments -> Bool
isB Arguments
x))
{-# INLINABLE takeBsArrSortedBy #-}

-- | For empty list of 'String's 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).
takeAsArrSortedBy
  :: (Arguments -> Arguments -> Ordering) -- ^ A 'compare'-like implementation for 'Arguments'. If needed you can implement your own 'Ord' instance for 'Arguments' and use it here. Here can be partial, just for 'A's.
  -> CLSpecifications
  -> [String]
  -> Array Int Arguments
takeAsArrSortedBy :: (Arguments -> Arguments -> Ordering)
-> CLSpecifications -> [String] -> Array Int Arguments
takeAsArrSortedBy = ((Arguments -> Arguments -> Ordering)
 -> CLSpecifications -> [String] -> Args)
-> (Arguments -> Arguments -> Ordering)
-> CLSpecifications
-> [String]
-> Array Int Arguments
takeABCsArrSortedBy ((Arguments -> Bool)
-> (Arguments -> Arguments -> Ordering)
-> CLSpecifications
-> [String]
-> Args
takeArgsSortedBy (\Arguments
x -> Arguments -> Bool
notNullArguments Arguments
x Bool -> Bool -> Bool
&& Arguments -> Bool
isA Arguments
x))
{-# INLINABLE takeAsArrSortedBy #-}