phonetic-languages-general-0.3.0.1: A generalization of the uniqueness-periods-vector-general functionality.
Copyright(c) OleksandrZhabenko 2020
LicenseMIT
Maintainerolexandr543@yahoo.com
StabilityExperimental
Safe HaskellNone
LanguageHaskell2010

Languages.UniquenessPeriods.Vector.General.DebugG

Description

Generalization of the functionality of the DobutokO.Poetry.General.Debug module from the dobutokO-poetry-general-languages package.

Synopsis

Pure functions

Self-recursive pure functions and connected with them ones

maximumElBy Source #

Arguments

:: (Eq a, Foldable t, InsertLeft t a, Monoid (t a), Monoid (t (t a)), Foldable t2, Ord b) 
=> Int

The quantity of the represented as functions "properties" to be applied from the second argument. The order is from the right to the left.

-> Vector (t2 b -> b)

Vector of the represented as functions "properties" to be applied consequently.

-> UniqG2T2 t t2 a b

The data to be analyzed.

-> UniquenessG1T2 t t2 a b

The maximum element in respect with the given parameters.

The function evaluates the Vector of UniquenessG1T2 t t2 a b elements (related with the third argument) to retrieve the possibly maximum element in it with respect to the order and significance (principality) of the "properties" (represented as the functions f :: [b] -> b) being evaluated. The most significant and principal is the "property", which index in the Vector of them is the Int argument (so it is the first one) of the function minus 1, then less significant is the next to the left "property" and so on. The predefined library "properties" or related to them functions can be found in the package phonetic-languages-properties.

uniqNPropertiesN Source #

Arguments

:: (Eq a, Foldable t, InsertLeft t a, Monoid (t a), Monoid (t (t a)), Foldable t2, Ord b, Show a, Show b) 
=> Int

A quantity of the recursive calls that returns each one a new resulting group from the rest of the data processed.

-> Int

The quantity of the represented as functions "properties" to be applied from the second argument. The order is from the right to the left.

-> Vector (t2 b -> b)

Vector of the represented as functions "properties" to be applied consequently.

-> UniqG2T2 t t2 a b

The data to be analyzed.

-> UniqG2T2 t t2 a b 

Finds out the n (the first Int argument) consequential maximum elements, and then rearranges the input moving the elements equal by the first element in the triple to the maximum element to the first element in the tuple.

uniqNPropertiesNAll Source #

Arguments

:: (Eq a, Foldable t, InsertLeft t a, Monoid (t a), Monoid (t (t a)), Foldable t2, Ord b, Show a, Show b) 
=> Int

A quantity of the recursive calls that returns each one a new resulting group from the rest of the data processed.

-> Vector (t2 b -> b)

Vector of the represented as functions "properties" to be applied consequently.

-> UniqG2T2 t t2 a b

The data to be analyzed.

-> UniqG2T2 t t2 a b 

A variant of the uniqNPropertiesN where all the given "properties" are used.

uniqNProperties2GN Source #

Arguments

:: (Eq a, Foldable t, InsertLeft t a, Monoid (t a), Monoid (t (t a)), Foldable t2, UGG1 t (PreApp t a) a, Ord b, Show a, Show b) 
=> a

The first most common element in the whitespace symbols structure

-> t a

A list of "whitespace symbols" that delimits the sublists in the list to be processed.

-> (t a -> Vector a)

The function that is used internally to convert to the boxed Vector of a so that the function can process further the permutations

-> (t (t a) -> Vector (Vector a))

The function that is used internally to convert to the boxed Vector of Vector of a so that the function can process further

-> (Vector a -> t a)

The function that is used internally to convert from the boxed Vector of a so that the function can process further

-> Vector (Vector Int)

The list of permutations of Int indices starting from 0 and up to n (n is probably less than 7).

-> PreApp t a

A parameter to specify the lists to be prepended and postpended to the given data to be processed before actual processment.

-> Int

A quantity of the recursive calls that returns each one a new resulting group from the rest of the data processed.

-> Int

The quantity of the represented as functions "properties" to be applied from the second argument. The order is from the right to the left.

-> Vector (t2 b -> b)

Vector of the represented as functions "properties" to be applied consequently.

-> FuncRep (t a) (Vector c) (t2 b)

It includes the defined earlier variant with data constructor D2, but additionally allows to use just single argument with data constructor U1

-> t a

The data to be processed.

-> UniqG2T2 t t2 a b 

The full analyzing and processment function.

Pure functions

maximumElByAll Source #

Arguments

:: (Eq a, Foldable t, InsertLeft t a, Monoid (t a), Monoid (t (t a)), Foldable t2, Ord b, Show a, Show b) 
=> Vector (t2 b -> b)

Vector of the represented as functions "properties" to be applied consequently.

-> UniqG2T2 t t2 a b

The data to be analyzed.

-> UniquenessG1T2 t t2 a b

The maximum element according to the given "properties".

Variant of the maximumElBy function where all the given "properties" are used. The predefined library "properties" or related to them functions can be found in the package uniqueness-periods-vector-properties.

maximumElGBy Source #

Arguments

:: (Eq a, Foldable t, InsertLeft t a, Monoid (t a), Monoid (t (t a)), Foldable t2, UGG1 t (PreApp t a) a, Ord b, Show a, Show b) 
=> t a

The "whitespace symbols" that delimit the subs in the Foldable structure to be processed.

-> a

The first "whitespace symbol" from the left.

-> PreApp t a

A parameter to specify the lists to be prepended and postpended to the given data to be processed before actual processment.

-> (t a -> Vector a)

The function that is used internally to convert to the boxed Vector of a so that the function can process further the permutations

-> (t (t a) -> Vector (Vector a))

The function that is used internally to convert to the boxed Vector of Vector of a so that the function can process further

-> (Vector a -> t a)

The function that is used internally to convert from the boxed Vector of a so that the function can process further

-> Vector (Vector Int)

The list of permutations of Int indices starting from 0 and up to n (n is probably less than 7).

-> Int

The quantity of the represented as functions "properties" to be applied from the second argument. The order is from the right to the left.

-> Vector (t2 b -> b)

Vector of the represented as functions "properties" to be applied consequently.

-> FuncRep (t a) (Vector c) (t2 b)

It includes the defined earlier variant with data constructor D2, but additionally allows to use just single argument with data constructor U1

-> t a

The data to be processed.

-> UniquenessG1T2 t t2 a b 

The function evaluates the generated Vector of UniquenessG1T2 t t2 a b elements to retrieve the possibly maximum element in it with respect to the order and significance (principality) of the "properties" being evaluated. The most significant and principal is the "property", which index in the Vector of them is the Int argument of the function minus 1, then less significant is the next to the left "property" and so on.

uniquenessVariantsGN Source #

Arguments

:: (Eq a, Foldable t, InsertLeft t a, Monoid (t a), Monoid (t (t a)), Foldable t2, Ord b, Show a, Show b) 
=> a

The first from the left element inthe "whitespace symbols" Foldable structure.

-> t a

A list of "whitespace symbols" that delimits the subGs in the structure to be processed.

-> (t a -> Vector a)

The function that is used internally to convert to the boxed Vector of a so that the function can process further the permutations

-> (t (t a) -> Vector (Vector a))

The function that is used internally to convert to the boxed Vector of Vector of a so that the function can process further

-> (Vector a -> t a)

The function that is used internally to convert from the boxed Vector of a so that the function can process further

-> Vector (Vector Int)

The list of permutations of Int indices starting from 0 and up to n (n is probably less than 7).

-> PreApp t a

A parameter to specify the lists to be prepended and postpended to the given data to be processed before actual processment.

-> Vector (t2 b -> b)

Vector of the represented as functions "properties" to be applied consequently.

-> FuncRep (t a) (Vector c) (t2 b)

It includes the defined earlier variant with data constructor D2, but additionally allows to use just single argument with data constructor U1

-> t a

The data to be processed.

-> Vector (UniquenessG1T2 t t2 a b) 

A variant for uniquenessVariants2GNB and uniquenessVariants2GNPB with the second argument defining, which one is used.

maximumElByVec Source #

Arguments

:: (Eq a, Foldable t, InsertLeft t a, Monoid (t a), Monoid (t (t a)), Foldable t2, Ord b, Show a, Show b) 
=> Int

The quantity of the represented as functions "properties" to be applied from the second argument. The order is from the right to the left.

-> Vector (t2 b -> b)

Vector of the represented as functions "properties" to be applied consequently.

-> UniqG2T2 t t2 a b

The data to be analyzed.

-> UniqG2T2 t t2 a b 

Rearranges the last argument. Finds out the group of maximum elements with respect of the k "properties" (the most significant of which is the rightest one, then to the left less significant etc.) of the second argument. The number of "properties" is given as the first argument. Then the function rearranges the last argument by moving the elements equal by the second element in the triple to the maximum element to the first element in the resulting tuple. The elements that are not equal to the maximum one are moved to the second element in the tuple. If the second element of the tuple is empty, then just returns the last argument.

The last by significance "property" is the first element in the Vector of "properties" ([b] -> b) (so that the order of significance is from the right to the left in the respective Vector). If the length of the vector of properties is greater than the first argument then the last element(s) in the vector do not participate in producing the result (are ignored).

maximumElByVecAll Source #

Arguments

:: (Eq a, Foldable t, InsertLeft t a, Monoid (t a), Monoid (t (t a)), Foldable t2, Ord b, Show a, Show b) 
=> Vector (t2 b -> b)

Vector of the represented as functions "properties" to be applied consequently.

-> UniqG2T2 t t2 a b

The data to be analyzed.

-> UniqG2T2 t t2 a b 

A variant of the maximumElByVec where all the given "properties" are used.

IO functions

Printing subsystem

toFile Source #

Arguments

:: (Foldable t, Show (t a), Monoid (t a)) 
=> FilePath

The FilePath to the file to be written in the AppendMode (actually appended with) the information output.

-> t (t a)

Each element is appended on the new line to the file.

-> IO () 

Prints every element from the structure on the new line to the file. Uses appendFile function inside.

toFileStr Source #

Arguments

:: FilePath

The FilePath to the file to be written in the AppendMode (actually appended with) the information output.

-> [String]

Each String is appended on the new line to the file.

-> IO () 

Prints every String from the list on the new line to the file. Uses appendFile function inside.

printUniquenessG1 Source #

Arguments

:: (Show (t a), Show b, Show (t2 b)) 
=> Info2

A parameter to control the predefined behaviour of the printing. The I1 branch prints to the stdout and the I2 - to the file.

-> UniquenessG1T2 t t2 a b

The element, for which the information is printed.

-> IO () 

Is used to print output specified to the stdout or to the FilePath specified as the inner argument in the Info2 parameter.

printUniquenessG1List Source #

Arguments

:: (Show (t a), Show b, Show (t2 b)) 
=> Info2

A parameter to control the predefined behaviour of the printing. The I1 branch prints to the stdout and the I2 - to the file.

-> [UniquenessG1T2 t t2 a b]

The list of elements, for which the information is printed.

-> IO () 

Is used to print output specified to the stdout or to the FilePath specified as the inner argument in the Info2 parameter.

With String-based arguments

printUniquenessG1ListStr Source #

Arguments

:: (Show b, Show (t2 b)) 
=> Info2

A parameter to control the predefined behaviour of the printing. The I1 branch prints to the stdout and the I2 - to the file.

-> Vector (UniquenessG1T2 [] t2 Char b)

The Vector of elements, for which the information is printed.

-> IO () 

A variant of the printUniquenessG1List where a is Char so that the inner third arguments in the triples are Strings.

With Vector Char based arguments

printUniquenessG1VChar Source #

Arguments

:: (Show b, Show (t2 b)) 
=> Info2

A parameter to control the predefined behaviour of the printing. The I1 branch prints to the stdout and the I2 - to the file.

-> Vector (UniquenessG1T2 Vector t2 Char b)

The Vector of elements, for which the information is printed.

-> IO () 

A variant of the printUniquenessG1List where a is Char so that the inner third arguments in the triples are Vector of Char.

Auxiliary functions

newLineEnding :: String Source #

Auxiliary printing function to define the line ending in some cases.

equalSnDs :: Ord b => Vector b -> Vector b -> Bool Source #