-- | -- Module : Phonetic.Languages.Permutations.ArrMini -- Copyright : (c) OleksandrZhabenko 2021 -- License : MIT -- Stability : Experimental -- Maintainer : olexandr543@yahoo.com -- -- Special permutations functions for the phonetic-languages series of packages. This -- module uses no vectors, but instead uses arrays. module Phonetic.Languages.Permutations.ArrMini ( genPairwisePermutations , pairsSwapP , genPairwisePermutationsArrN , genPairwisePermutationsArr , genPairwisePermutationsLN , genPairwisePermutationsL , genPairwisePermutationsArrLN , genPairwisePermutationsArrL ) where import GHC.Arr genPairwisePermutations :: Int -> Array Int [Int] genPairwisePermutations n = listArray (0,(n*(n-1)) `quot` 2) . pairsSwapP . take n $ [0..] {-# INLINE genPairwisePermutations #-} pairsSwapP :: [Int] -> [[Int]] pairsSwapP xs = xs:[swap2Ls k m xs | k <- xs, m <- xs , k < m] {-# INLINABLE pairsSwapP #-} -- | The first two arguments are considered not equal, though it is not checked. swap2ns :: Int -> Int -> Int -> Int swap2ns k m n | n /= k = if n /= m then n else k | otherwise = m {-# INLINE swap2ns #-} swap2Ls :: Int -> Int -> [Int] -> [Int] swap2Ls k m = map (swap2ns k m) {-# INLINE swap2Ls #-} genPairwisePermutationsArrN :: Int -> Array Int (Array Int [Int]) genPairwisePermutationsArrN n = amap genPairwisePermutations . listArray (0,n - 2) $ [2..n] {-# INLINE genPairwisePermutationsArrN #-} genPairwisePermutationsArr :: Array Int (Array Int [Int]) genPairwisePermutationsArr = genPairwisePermutationsArrN 10 {-# INLINE genPairwisePermutationsArr #-} genPairwisePermutationsLN :: Int -> [Array Int Int] genPairwisePermutationsLN n = map (\xs -> listArray (0,n - 1) xs) . pairsSwapP . take n $ [0..] {-# INLINE genPairwisePermutationsLN #-} genPairwisePermutationsL :: [Array Int Int] genPairwisePermutationsL = genPairwisePermutationsLN 10 {-# INLINE genPairwisePermutationsL #-} genPairwisePermutationsArrLN :: Int -> Array Int [Array Int Int] genPairwisePermutationsArrLN n = amap genPairwisePermutationsLN . listArray (0,n - 2) $ [2..n] {-# INLINE genPairwisePermutationsArrLN #-} genPairwisePermutationsArrL :: Array Int [Array Int Int] genPairwisePermutationsArrL = genPairwisePermutationsArrLN 10 {-# INLINE genPairwisePermutationsArrL #-}