{-# LANGUAGE MultiWayIf #-} -- | -- Module : Phonetic.Languages.Permutations.ArrMini1 -- Copyright : (c) OleksandrZhabenko 2022 -- 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.ArrMini1 ( genElementaryPermutations1 , pairsSwapP1 , genElementaryPermutationsArrN1 , genElementaryPermutationsArr1 , genElementaryPermutationsLN1 , genElementaryPermutationsL1 , genElementaryPermutationsArrLN1 , genElementaryPermutationsArrL1 ) where import GHC.Arr genElementaryPermutations1 :: Int -> Array Int [Int] genElementaryPermutations1 n = listArray (0,l-1) xs where xs = pairsSwapP1 . take n $ [0..] l = length xs {-# INLINE genElementaryPermutations1 #-} pairsSwapP1 :: [Int] -> [[Int]] pairsSwapP1 xs = xs:[swap2Ls1 k m xs | k <- xs, m <- xs , abs (k - m) > 1] `mappend` [swap2Ls1 k (k - 1) xs | k <- drop 1 xs ] {-# INLINABLE pairsSwapP1 #-} -- | The first two arguments are considered not equal and all three of the arguments are considered greater or equal to 0, though it is not checked. swap2ns1 :: Int -> Int -> Int -> Int swap2ns1 k n m | n > k = if | m < k -> m | m > n -> m | m >= k && m < n -> m + 1 | otherwise -> k | otherwise = if | m > k -> m | m < n -> m | m <= k && m > n -> m - 1 | otherwise -> k {-# INLINE swap2ns1 #-} swap2Ls1 :: Int -> Int -> [Int] -> [Int] swap2Ls1 k m = map (swap2ns1 k m) {-# INLINE swap2Ls1 #-} genElementaryPermutationsArrN1 :: Int -> Array Int (Array Int [Int]) genElementaryPermutationsArrN1 n = amap genElementaryPermutations1 . listArray (0,n - 2) $ [2..n] {-# INLINE genElementaryPermutationsArrN1 #-} genElementaryPermutationsArr1 :: Array Int (Array Int [Int]) genElementaryPermutationsArr1 = genElementaryPermutationsArrN1 10 {-# INLINE genElementaryPermutationsArr1 #-} genElementaryPermutationsLN1 :: Int -> [Array Int Int] genElementaryPermutationsLN1 n = map (\xs -> listArray (0,n - 1) xs) . pairsSwapP1 . take n $ [0..] {-# INLINE genElementaryPermutationsLN1 #-} genElementaryPermutationsL1 :: [Array Int Int] genElementaryPermutationsL1 = genElementaryPermutationsLN1 10 {-# INLINE genElementaryPermutationsL1 #-} genElementaryPermutationsArrLN1 :: Int -> Array Int [Array Int Int] genElementaryPermutationsArrLN1 n = amap genElementaryPermutationsLN1 . listArray (0,n - 2) $ [2..n] {-# INLINE genElementaryPermutationsArrLN1 #-} genElementaryPermutationsArrL1 :: Array Int [Array Int Int] genElementaryPermutationsArrL1 = genElementaryPermutationsArrLN1 10 {-# INLINE genElementaryPermutationsArrL1 #-}