{-# OPTIONS_HADDOCK show-extensions #-}

-- |
-- Module      :  Languages.UniquenessPeriods.Array.Constraints
-- Copyright   :  (c) OleksandrZhabenko 2020-2022
-- License     :  MIT
-- Stability   :  Experimental
-- Maintainer  :  olexandr543@yahoo.com
--
-- Provides several the most important variants of constraints for the
-- permutations. All the 'Array'
-- here must consists of unique 'Int' starting from 0 to n and the 'Int'
-- arguments must be in the range [0..n] though these inner constraints are
-- not checked. It is up to user to check them.
-- Uses arrays instead of vectors.

{-# LANGUAGE BangPatterns, FlexibleContexts #-}

module Languages.UniquenessPeriods.Array.Constraints (
  -- * Basic predicate
  unsafeOrderIJ
  -- * Functions to work with permutations with basic constraints ('Array'-based)
  , filterOrderIJ
  , unsafeTriples
  , unsafeQuadruples
  -- ** With multiple elements specified
  , unsafeSeveralA
  , unsafeSeveralB
  -- ** With fixed points
  , fixedPointsG
  , fixedPointsS
) where

import Data.Maybe (fromJust)
import Data.SubG (InsertLeft(..),filterG)
import GHC.Arr
import Data.Foldable (foldl')

-- | Being given the data satisfying the constraints in the module header checks whether in the 'Array' the first argument stands before the second one.
unsafeOrderIJ :: Int -> Int -> Array Int Int -> Bool
unsafeOrderIJ :: Int -> Int -> Array Int Int -> Bool
unsafeOrderIJ Int
i Int
j = (\(Int
_,Int
_,Integer
r) -> if Integer
r Integer -> Integer -> Bool
forall a. Eq a => a -> a -> Bool
== Integer
0 then Bool
True else Bool
False) ((Int, Int, Integer) -> Bool)
-> (Array Int Int -> (Int, Int, Integer)) -> Array Int Int -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ((Int, Int, Integer) -> Int -> (Int, Int, Integer))
-> (Int, Int, Integer) -> Array Int Int -> (Int, Int, Integer)
forall (t :: * -> *) b a.
Foldable t =>
(b -> a -> b) -> b -> t a -> b
foldl' (Int, Int, Integer) -> Int -> (Int, Int, Integer)
forall c a. (Num c, Eq a, Eq c) => (a, a, c) -> a -> (a, a, c)
helpG (Int
i,Int
j,Integer
0)

helpG :: (a, a, c) -> a -> (a, a, c)
helpG (a
t,a
u,c
n) a
z
  | a
z a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
t = (a
t,a
u,c
1)
  | a
z a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
u =
     case c
n of
      c
0 -> (a
t,a
u,c
2)
      c
_ -> (a
t,a
u,c
n c -> c -> c
forall a. Num a => a -> a -> a
- c
1)
  | Bool
otherwise = (a
t,a
u,c
n)
{-# INLINE helpG #-}

-- | Being given the data satisfying the constraints in the module header returns the elements that satisfy 'unsafeOrderIJ' as a predicate.
filterOrderIJ :: (InsertLeft t (Array Int Int), Monoid (t (Array Int Int))) => Int -> Int -> t (Array Int Int) -> t (Array Int Int)
filterOrderIJ :: Int -> Int -> t (Array Int Int) -> t (Array Int Int)
filterOrderIJ Int
i Int
j = (Array Int Int -> Bool) -> t (Array Int Int) -> t (Array Int Int)
forall (t :: * -> *) a.
(InsertLeft t a, Monoid (t a)) =>
(a -> Bool) -> t a -> t a
filterG (Int -> Int -> Array Int Int -> Bool
unsafeOrderIJ Int
i Int
j)

-- | Being given the data satisfying the constraints in the module header reduces the number of further computations in the foldable structure of
-- the permutations each one being represented as 'Array' 'Int' 'Int' where the elements are all the numbers in the range [0..n] without duplication if the
-- arguments are the indeces of the duplicated words or their concatenated combinations in the corresponding line.
-- The first three arguments
-- are the indices of the the triple duplicated elements (words or their concatenated combinations in the @phonetic-languages@ series of packages).
unsafeTriples :: (InsertLeft t (Array Int Int), Monoid (t (Array Int Int))) => Int -> Int -> Int -> t (Array Int Int) -> t (Array Int Int)
unsafeTriples :: Int -> Int -> Int -> t (Array Int Int) -> t (Array Int Int)
unsafeTriples Int
i Int
j Int
k = (Array Int Int -> Bool) -> t (Array Int Int) -> t (Array Int Int)
forall (t :: * -> *) a.
(InsertLeft t a, Monoid (t a)) =>
(a -> Bool) -> t a -> t a
filterG (\Array Int Int
v -> Int -> Int -> Array Int Int -> Bool
unsafeOrderIJ Int
i Int
j Array Int Int
v Bool -> Bool -> Bool
&& Int -> Int -> Array Int Int -> Bool
unsafeOrderIJ Int
j Int
k Array Int Int
v)

-- | Being given the data satisfying the constraints in the module header reduces the number of further computations in the foldable structure of
-- the permutations each one being represented as 'Array' 'Int' 'Int' where the elements are all the numbers in the range [0..n] without duplication if the
-- arguments are the indeces of the duplicated words or their concatenated combinations in the corresponding line.
-- The first four arguments
-- are the indices of the the quadruple duplicated elements (words or their concatenated combinations in the @phonetic-languages@ series of packages).
unsafeQuadruples :: (InsertLeft t (Array Int Int), Monoid (t (Array Int Int))) => Int -> Int -> Int -> Int -> t (Array Int Int) -> t (Array Int Int)
unsafeQuadruples :: Int -> Int -> Int -> Int -> t (Array Int Int) -> t (Array Int Int)
unsafeQuadruples Int
i Int
j Int
k Int
l = (Array Int Int -> Bool) -> t (Array Int Int) -> t (Array Int Int)
forall (t :: * -> *) a.
(InsertLeft t a, Monoid (t a)) =>
(a -> Bool) -> t a -> t a
filterG (\Array Int Int
v -> Int -> Int -> Array Int Int -> Bool
unsafeOrderIJ Int
i Int
j Array Int Int
v Bool -> Bool -> Bool
&& Int -> Int -> Array Int Int -> Bool
unsafeOrderIJ Int
j Int
k Array Int Int
v Bool -> Bool -> Bool
&& Int -> Int -> Array Int Int -> Bool
unsafeOrderIJ Int
k Int
l Array Int Int
v)

-- | Being given the data satisfying the constraints in the module header reduces the number of further computations in the foldable structure of
-- the permutations each one being represented as 'Array' 'Int' 'Int' where the elements are all the numbers in the range [0..n] without duplication.
-- The first argument
-- is the index of the the element (a word or their concatenated combination in the @phonetic-languages@ series of packages), the second argument
-- is 'Array' 'Int' of indices that are in the range [0..n]. Filters (and reduces further complex computations) the permutations so that only the
-- variants with the indices in the second argument all stand AFTER the element with the index equal to the first argument.
unsafeSeveralA :: (InsertLeft t (Array Int Int), Monoid (t (Array Int Int))) => Int -> Array Int Int -> t (Array Int Int) -> t (Array Int Int)
unsafeSeveralA :: Int -> Array Int Int -> t (Array Int Int) -> t (Array Int Int)
unsafeSeveralA !Int
i0 Array Int Int
arr t (Array Int Int)
x = (Array Int Int -> Bool) -> t (Array Int Int) -> t (Array Int Int)
forall (t :: * -> *) a.
(InsertLeft t a, Monoid (t a)) =>
(a -> Bool) -> t a -> t a
filterG (Int -> Array Int Int -> Array Int Int -> Bool
forall (t :: * -> *).
Foldable t =>
Int -> t Int -> Array Int Int -> Bool
g Int
i0 Array Int Int
arr) t (Array Int Int)
x
   where g :: Int -> t Int -> Array Int Int -> Bool
g !Int
i0 !t Int
arr1 Array Int Int
arr2 = (Int -> Bool) -> t Int -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (\Int
k -> Int -> Int -> Array Int Int -> Bool
unsafeOrderIJ Int
i0 Int
k Array Int Int
arr2) t Int
arr1

-- | Being given the data satisfying the constraints in the module header reduces the number of further computations in the foldable structure of
-- the permutations each one being represented as 'Array' 'Int' 'Int' where the elements are all the numbers in the range [0..n] without duplication.
-- The first argument
-- is the index of the the element (a word or their concatenated combination in the @phonetic-languages@ series of packages), the second argument
-- is 'Array' of indices that are in the range [0..n]. Filters (and reduces further complex computations) the permutations so that only the
-- variants with the indices in the second argument all stand BEFORE the element with the index equal to the first argument.
unsafeSeveralB :: (InsertLeft t (Array Int Int), Monoid (t (Array Int Int))) => Int -> Array Int Int -> t (Array Int Int) -> t (Array Int Int)
unsafeSeveralB :: Int -> Array Int Int -> t (Array Int Int) -> t (Array Int Int)
unsafeSeveralB !Int
i0 Array Int Int
arr t (Array Int Int)
x = (Array Int Int -> Bool) -> t (Array Int Int) -> t (Array Int Int)
forall (t :: * -> *) a.
(InsertLeft t a, Monoid (t a)) =>
(a -> Bool) -> t a -> t a
filterG (Int -> Array Int Int -> Array Int Int -> Bool
forall (t :: * -> *).
Foldable t =>
Int -> t Int -> Array Int Int -> Bool
g Int
i0 Array Int Int
arr) t (Array Int Int)
x
   where g :: Int -> t Int -> Array Int Int -> Bool
g !Int
i0 !t Int
arr1 Array Int Int
arr2 = (Int -> Bool) -> t Int -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (\Int
k -> Int -> Int -> Array Int Int -> Bool
unsafeOrderIJ Int
k Int
i0 Array Int Int
arr2) t Int
arr1

--------------------------------------------------------------------------------

-- | Reduces the number of permutations using filtering leaving just those ones permutations where elements on the
-- first elements in the tuples in the first argument 'Array' places are moved to the places indexed with the second
-- elements in the tuples respectively.
fixedPointsG :: (InsertLeft t (Array Int Int), Monoid (t (Array Int Int))) => Array Int (Int,Int) -> t (Array Int Int) -> t (Array Int Int)
fixedPointsG :: Array Int (Int, Int) -> t (Array Int Int) -> t (Array Int Int)
fixedPointsG Array Int (Int, Int)
arr t (Array Int Int)
xs = (Array Int Int -> Bool) -> t (Array Int Int) -> t (Array Int Int)
forall (t :: * -> *) a.
(InsertLeft t a, Monoid (t a)) =>
(a -> Bool) -> t a -> t a
filterG (Array Int (Int, Int) -> Array Int Int -> Bool
forall (t :: * -> *) a i.
(Foldable t, Eq a) =>
t (Int, a) -> Array i a -> Bool
f Array Int (Int, Int)
arr) t (Array Int Int)
xs
   where f :: t (Int, a) -> Array i a -> Bool
f t (Int, a)
arr1 Array i a
arr2 = ((Int, a) -> Bool) -> t (Int, a) -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (\(Int
k,a
j) -> Array i a -> Int -> a
forall i e. Array i e -> Int -> e
unsafeAt Array i a
arr2 Int
k a -> a -> Bool
forall a. Eq a => a -> a -> Bool
== a
j) t (Int, a)
arr1

-- | A simplified variant of the 'fixedPointsG' function where the specified elements stay on their place and that is
-- why are 'fixed points' in the permutation specified.
fixedPointsS :: (InsertLeft t (Array Int Int), Monoid (t (Array Int Int))) => Array Int Int -> t (Array Int Int) -> t (Array Int Int)
fixedPointsS :: Array Int Int -> t (Array Int Int) -> t (Array Int Int)
fixedPointsS Array Int Int
arr t (Array Int Int)
xs = (Array Int Int -> Bool) -> t (Array Int Int) -> t (Array Int Int)
forall (t :: * -> *) a.
(InsertLeft t a, Monoid (t a)) =>
(a -> Bool) -> t a -> t a
filterG (Array Int Int -> Array Int Int -> Bool
forall (t :: * -> *) i. Foldable t => t Int -> Array i Int -> Bool
f Array Int Int
arr) t (Array Int Int)
xs
   where f :: t Int -> Array i Int -> Bool
f t Int
arr1 Array i Int
arr2 = (Int -> Bool) -> t Int -> Bool
forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (\Int
k -> Array i Int -> Int -> Int
forall i e. Array i e -> Int -> e
unsafeAt Array i Int
arr2 Int
k Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
k) t Int
arr1