{-# OPTIONS_HADDOCK show-extensions #-} -- | -- Module : Phonetic.Languages.Simplified.StrictVG.Base -- Copyright : (c) OleksandrZhabenko 2020-2021 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- Simplified version of the @phonetic-languages-common@ package. -- Uses less dependencies. {-# LANGUAGE BangPatterns #-} module Phonetic.Languages.Simplified.StrictVG.Base ( -- * Working with lists uniquenessVariants2GNBL , uniquenessVariants2GNPBL ) where import Phonetic.Languages.Permutations.Arr import Phonetic.Languages.Simplified.DataG.Base import qualified Data.Foldable as F import Data.SubG import GHC.Arr import Data.Monoid uniquenessVariants2GNBL :: (Eq a, Foldable t, InsertLeft t a, Monoid (t a), Monoid (t (t a))) => a -- ^ The first most common element in the \"whitespace symbols\" structure -> (t a -> [a]) -- ^ The function that is used internally to convert to the @[a]@ so that the function can process further the permutations -> ((t (t a)) -> [[a]]) -- ^ The function that is used internally to convert to the @[[a]]@ so that the function can process further -> ([a] -> t a) -- ^ The function that is used internally to convert to the needed representation so that the function can process further -> [Array Int Int] -- ^ The permutations of 'Int' indices starting from 0 and up to n (n is probably less than 8). -> t (t a) -- ^ Must be obtained as 'subG' @whspss xs@ -> [t a] uniquenessVariants2GNBL !hd f1 f2 f3 perms !subs = uniquenessVariants2GNPBL mempty mempty hd f1 f2 f3 perms subs {-# INLINE uniquenessVariants2GNBL #-} uniquenessVariants2GNPBL :: (Eq a, Foldable t, InsertLeft t a, Monoid (t a), Monoid (t (t a))) => t a -> t a -> a -- ^ The first most common element in the whitespace symbols structure -> (t a -> [a]) -- ^ The function that is used internally to convert to the @[a]@ so that the function can process further the permutations -> ((t (t a)) -> [[a]]) -- ^ The function that is used internally to convert to the @[[a]]@ so that the function can process further -> ([a] -> t a) -- ^ The function that is used internally to convert to the needed representation that the function can process further -> [Array Int Int] -- ^ The permutations of 'Int' indices starting from 0 and up to n (n is probably less than 8). -> t (t a) -- ^ Must be obtained as @subG whspss xs@ -> [t a] uniquenessVariants2GNPBL !ts !us !hd f1 f2 f3 perms !subs | F.null subs = mempty | otherwise = map f3 ns where !uss = (hd %@ us) %^ mempty !base0 = map (hd %@) . f2 $ subs !l = length base0 !baseArr = listArray (0,l - 1) base0 !ns = universalSetGL ts uss f1 f2 perms baseArr -- in map f3 ns {-# INLINE uniquenessVariants2GNPBL #-}