-- |
-- 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 :: Int -> Array Int [Int]
genPairwisePermutations Int
n = (Int, Int) -> [[Int]] -> Array Int [Int]
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0,(Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
*(Int
nInt -> Int -> Int
forall a. Num a => a -> a -> a
-Int
1)) Int -> Int -> Int
forall a. Integral a => a -> a -> a
`quot` Int
2) ([[Int]] -> Array Int [Int])
-> ([Int] -> [[Int]]) -> [Int] -> Array Int [Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> [[Int]]
pairsSwapP ([Int] -> [[Int]]) -> ([Int] -> [Int]) -> [Int] -> [[Int]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
n ([Int] -> Array Int [Int]) -> [Int] -> Array Int [Int]
forall a b. (a -> b) -> a -> b
$ [Int
0..]
{-# INLINE genPairwisePermutations #-}

pairsSwapP :: [Int] -> [[Int]]
pairsSwapP :: [Int] -> [[Int]]
pairsSwapP [Int]
xs = [Int]
xs[Int] -> [[Int]] -> [[Int]]
forall a. a -> [a] -> [a]
:[Int -> Int -> [Int] -> [Int]
swap2Ls Int
k Int
m [Int]
xs | Int
k <- [Int]
xs, Int
m <- [Int]
xs , Int
k Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
< Int
m]
{-# INLINABLE pairsSwapP #-}

-- | The first two arguments are considered not equal, though it is not checked.
swap2ns :: Int -> Int -> Int -> Int
swap2ns :: Int -> Int -> Int -> Int
swap2ns Int
k Int
m Int
n
 | Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
k = if Int
n Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= Int
m then Int
n else Int
k
 | Bool
otherwise = Int
m
{-# INLINE swap2ns #-}

swap2Ls :: Int -> Int -> [Int] -> [Int]
swap2Ls :: Int -> Int -> [Int] -> [Int]
swap2Ls Int
k Int
m = (Int -> Int) -> [Int] -> [Int]
forall a b. (a -> b) -> [a] -> [b]
map (Int -> Int -> Int -> Int
swap2ns Int
k Int
m)
{-# INLINE swap2Ls #-}

genPairwisePermutationsArrN :: Int -> Array Int (Array Int [Int])
genPairwisePermutationsArrN :: Int -> Array Int (Array Int [Int])
genPairwisePermutationsArrN Int
n = (Int -> Array Int [Int])
-> Array Int Int -> Array Int (Array Int [Int])
forall a b i. (a -> b) -> Array i a -> Array i b
amap Int -> Array Int [Int]
genPairwisePermutations (Array Int Int -> Array Int (Array Int [Int]))
-> ([Int] -> Array Int Int) -> [Int] -> Array Int (Array Int [Int])
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int, Int) -> [Int] -> Array Int Int
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0,Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
2) ([Int] -> Array Int (Array Int [Int]))
-> [Int] -> Array Int (Array Int [Int])
forall a b. (a -> b) -> a -> b
$ [Int
2..Int
n]
{-# INLINE genPairwisePermutationsArrN #-}

genPairwisePermutationsArr :: Array Int (Array Int [Int])
genPairwisePermutationsArr :: Array Int (Array Int [Int])
genPairwisePermutationsArr = Int -> Array Int (Array Int [Int])
genPairwisePermutationsArrN Int
10
{-# INLINE genPairwisePermutationsArr #-}

genPairwisePermutationsLN :: Int -> [Array Int Int]
genPairwisePermutationsLN :: Int -> [Array Int Int]
genPairwisePermutationsLN Int
n = ([Int] -> Array Int Int) -> [[Int]] -> [Array Int Int]
forall a b. (a -> b) -> [a] -> [b]
map (\[Int]
xs -> (Int, Int) -> [Int] -> Array Int Int
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0,Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
1) [Int]
xs) ([[Int]] -> [Array Int Int])
-> ([Int] -> [[Int]]) -> [Int] -> [Array Int Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [Int] -> [[Int]]
pairsSwapP ([Int] -> [[Int]]) -> ([Int] -> [Int]) -> [Int] -> [[Int]]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> [Int] -> [Int]
forall a. Int -> [a] -> [a]
take Int
n ([Int] -> [Array Int Int]) -> [Int] -> [Array Int Int]
forall a b. (a -> b) -> a -> b
$ [Int
0..]
{-# INLINE genPairwisePermutationsLN #-}

genPairwisePermutationsL :: [Array Int Int]
genPairwisePermutationsL :: [Array Int Int]
genPairwisePermutationsL = Int -> [Array Int Int]
genPairwisePermutationsLN Int
10
{-# INLINE genPairwisePermutationsL #-}

genPairwisePermutationsArrLN :: Int -> Array Int [Array Int Int]
genPairwisePermutationsArrLN :: Int -> Array Int [Array Int Int]
genPairwisePermutationsArrLN Int
n = (Int -> [Array Int Int])
-> Array Int Int -> Array Int [Array Int Int]
forall a b i. (a -> b) -> Array i a -> Array i b
amap Int -> [Array Int Int]
genPairwisePermutationsLN (Array Int Int -> Array Int [Array Int Int])
-> ([Int] -> Array Int Int) -> [Int] -> Array Int [Array Int Int]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. (Int, Int) -> [Int] -> Array Int Int
forall i e. Ix i => (i, i) -> [e] -> Array i e
listArray (Int
0,Int
n Int -> Int -> Int
forall a. Num a => a -> a -> a
- Int
2) ([Int] -> Array Int [Array Int Int])
-> [Int] -> Array Int [Array Int Int]
forall a b. (a -> b) -> a -> b
$ [Int
2..Int
n]
{-# INLINE genPairwisePermutationsArrLN #-}

genPairwisePermutationsArrL :: Array Int [Array Int Int]
genPairwisePermutationsArrL :: Array Int [Array Int Int]
genPairwisePermutationsArrL = Int -> Array Int [Array Int Int]
genPairwisePermutationsArrLN Int
10
{-# INLINE genPairwisePermutationsArrL #-}