-- | -- Module : Phonetic.Languages.Permutations.Arr -- Copyright : (c) OleksandrZhabenko 2020-2021 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- Permutations and universal set functions for the phonetic-languages series of packages. This -- module uses no vectors, but instead uses arrays. module Phonetic.Languages.Permutations.Arr ( universalSetGL , genPermutations , genPermutationsArr , genPermutationsL , genPermutationsArrL ) where import GHC.Arr import qualified Data.List as L (permutations) import Data.SubG import qualified Data.Foldable as F (concat,foldr',foldl') import Data.Monoid -- | A key point of the evaluation -- the universal set of the task represented as a @[[a]]@. universalSetGL :: (Eq a, Foldable t, InsertLeft t a, Monoid (t a), Monoid (t (t a))) => t a -> t (t a) -> (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 needed representation so that the function can process further -> [Array Int Int] -- ^ The list of permutations of 'Int' indices starting from 0 and up to n (n is probably less than 7). -> Array Int [a] -> [[a]] universalSetGL ts uss f1 f2 permsL baseArr = map (F.concat . F.foldr' (:) [] . (f1 ts:) . (`mappend` f2 uss) . elems . amap (unsafeAt baseArr)) permsL {-# INLINE universalSetGL #-} -- | One of the popular examples: realization of the factorial function using 'F.foldl''. Is taken from some -- teaching material. factorial n = F.foldl' (*) 1 [1..n] genPermutations :: Int -> Array Int [Int] genPermutations n = listArray (0,factorial n - 1) . L.permutations . take n $ [0..] {-# INLINE genPermutations #-} genPermutationsArr :: Array Int (Array Int [Int]) genPermutationsArr = amap genPermutations . listArray (0,5) $ [2..7] {-# INLINE genPermutationsArr #-} genPermutationsL :: Int -> [Array Int Int] genPermutationsL n = map (\xs -> listArray (0,n - 1) xs) . L.permutations . take n $ [0..] {-# INLINE genPermutationsL #-} genPermutationsArrL :: Array Int [Array Int Int] genPermutationsArrL = amap genPermutationsL . listArray (0,5) $ [2..7] {-# INLINE genPermutationsArrL #-}