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

Languages.UniquenessPeriods.Vector.DataG

Description

Is a generalization of the DobutokO.Poetry.Data module functionality from the dobutokO-poetry-general package.

Synopsis

Documentation

type UniquenessG1T2 t t2 a b = (t2 b, Vector b, t a) Source #

data PreApp t a Source #

The list in the PA variant represent the prepending [a] and the postpending one respectively. K constuctor actually means no prepending and postpending (usually of the text). Both are used basically to control the behaviour of the functions.

Constructors

K 
PA (t a) (t a) 

Instances

Instances details
Eq a => UGG1 [] (PreApp [] a) a Source # 
Instance details

Defined in Languages.UniquenessPeriods.Vector.DataG

Methods

get1m :: PreApp [] a -> [a] Source #

get2m :: PreApp [] a -> [a] Source #

getm :: Bool -> PreApp [] a -> [a] Source #

preapp :: PreApp [] a -> [[a]] -> [[a]] Source #

setm :: [a] -> [a] -> PreApp [] a Source #

Eq a => UGG1 Vector (PreApp Vector a) a Source # 
Instance details

Defined in Languages.UniquenessPeriods.Vector.DataG

Eq (t a) => Eq (PreApp t a) Source # 
Instance details

Defined in Languages.UniquenessPeriods.Vector.DataG

Methods

(==) :: PreApp t a -> PreApp t a -> Bool #

(/=) :: PreApp t a -> PreApp t a -> Bool #

class Foldable t => UGG1 t a b where Source #

Minimal complete definition

get1m, get2m, preapp, setm

Methods

get1m :: a -> t b Source #

get2m :: a -> t b Source #

getm :: Bool -> a -> t b Source #

preapp :: a -> t (t b) -> t (t b) Source #

setm :: t b -> t b -> a Source #

Instances

Instances details
Eq a => UGG1 [] (PreApp [] a) a Source # 
Instance details

Defined in Languages.UniquenessPeriods.Vector.DataG

Methods

get1m :: PreApp [] a -> [a] Source #

get2m :: PreApp [] a -> [a] Source #

getm :: Bool -> PreApp [] a -> [a] Source #

preapp :: PreApp [] a -> [[a]] -> [[a]] Source #

setm :: [a] -> [a] -> PreApp [] a Source #

Eq a => UGG1 Vector (PreApp Vector a) a Source # 
Instance details

Defined in Languages.UniquenessPeriods.Vector.DataG

isPA :: PreApp t a -> Bool Source #

isK :: PreApp t a -> Bool Source #

data UniquenessG2 a b Source #

Constructors

UL2 (Vector a, b) 

Instances

Instances details
(Eq a, Eq b) => Eq (UniquenessG2 a b) Source # 
Instance details

Defined in Languages.UniquenessPeriods.Vector.DataG

Methods

(==) :: UniquenessG2 a b -> UniquenessG2 a b -> Bool #

(/=) :: UniquenessG2 a b -> UniquenessG2 a b -> Bool #

(Show a, Show b, InsertLeft t a, Foldable t2, Show (t2 b), Show (t a)) => Show (UniquenessG2 (UniquenessG1T2 t t2 a b) (Vector (UniquenessG1T2 t t2 a b))) Source # 
Instance details

Defined in Languages.UniquenessPeriods.Vector.DataG

Methods

showsPrec :: Int -> UniquenessG2 (UniquenessG1T2 t t2 a b) (Vector (UniquenessG1T2 t t2 a b)) -> ShowS #

show :: UniquenessG2 (UniquenessG1T2 t t2 a b) (Vector (UniquenessG1T2 t t2 a b)) -> String #

showList :: [UniquenessG2 (UniquenessG1T2 t t2 a b) (Vector (UniquenessG1T2 t t2 a b))] -> ShowS #

type UniqG2T2 t t2 a b = UniquenessG2 (UniquenessG1T2 t t2 a b) (Vector (UniquenessG1T2 t t2 a b)) Source #

get22 :: UniqG2T2 t t2 a b -> (Vector (UniquenessG1T2 t t2 a b), Vector (UniquenessG1T2 t t2 a b)) Source #

data FuncRep a b c Source #

Is used to avoid significant code duplication.

Constructors

U1 (a -> c) 
D2 (a -> b) (b -> c) 

getAC :: FuncRep a b c -> a -> c Source #

isU1 :: FuncRep a b c -> Bool Source #

isD2 :: FuncRep a b c -> Bool Source #