{-# OPTIONS_HADDOCK show-extensions #-}

-- |
-- Module      :  Pladiprelio.Constraints
-- Copyright   :  (c) OleksandrZhabenko 2020-2023
-- License     :  MIT
-- Stability   :  Experimental
-- Maintainer  :  oleksandr.zhabenko@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.
-- The word \"unsafe\" in the names means that there is no checking whether the arguments are 
-- within the elements of the arrays, this checking is intended to be done elsewhere before applying 
-- the functions here. Without such a checking the result are meaningless.

{-# LANGUAGE BangPatterns, FlexibleContexts, NoImplicitPrelude #-}

module Phladiprelio.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
  -- * Distances between elements
  , unsafeSignDistanceIJ
  , unsafeUnsignDistanceIJ
  , filterSignDistanceIJ
  , filterUnsignDistanceIJ
  , filterSignDistanceIJK3
  , filterUnsignDistanceIJK3
  , filterMixedDistanceIJK3
) where

import GHC.Base hiding (foldr)
import GHC.Num ((-),(+))
import Data.Maybe (fromJust)
import Data.SubG (InsertLeft(..),filterG)
import GHC.Arr
import Data.Foldable (all, foldr)

-- | 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 forall a. Eq a => a -> a -> Bool
== Integer
0 then Bool
True else Bool
False) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall {c} {a}. (Num c, Eq a, Eq c) => a -> (a, a, c) -> (a, a, c)
helpG (Int
j,Int
i,Integer
0)

helpG :: a -> (a, a, c) -> (a, a, c)
helpG a
z (a
t,a
u,c
n)
  | a
z forall a. Eq a => a -> a -> Bool
== a
t = (a
t,a
u,c
1)
  | a
z 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 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 checks whether in the
-- 'Array' the distance between positions of the first two arguments values is equal to the signed 
-- third argument.
unsafeSignDistanceIJ 
  :: Int 
  -> Int 
  -> Int -- ^ Can be of both signs, but not equal to 0. The positive value gives 'True' for the first argument being find earlier in the 'Array' than the second and the distance between their positions are equal to 'abs' @d@ (this argument). The negative value gives 'True' for the second argument  being earlier in the 'Array' than the first one and the distance between their positions are equal to 'abs' @d@ (this argument).
  -> Array Int Int 
  -> Bool
unsafeSignDistanceIJ :: Int -> Int -> Int -> Array Int Int -> Bool
unsafeSignDistanceIJ Int
i Int
j Int
d = (\(Int
_,Int
_,Int
r) -> if Int
r forall a. Ord a => a -> a -> Bool
> Int
100 then (Int
100 forall a. Num a => a -> a -> a
- Int
r) forall a. Eq a => a -> a -> Bool
== Int
d else Int
r forall a. Eq a => a -> a -> Bool
== Int
d) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall {c} {a}.
(Ord c, Ord a, Num c, Num a) =>
a -> (a, a, c) -> (a, a, c)
helpG2 (Int
j, Int
i, -Int
1)

helpG2 :: a -> (a, a, c) -> (a, a, c)
helpG2 a
z (a
t, a
u, c
n)
  | c
n forall a. Ord a => a -> a -> Bool
< c
0 = if (a
z forall a. Eq a => a -> a -> Bool
/= a
t Bool -> Bool -> Bool
&& a
z forall a. Eq a => a -> a -> Bool
/= a
u) then (a
t, a
u, c
n) else (a
t, a
u, if a
z forall a. Eq a => a -> a -> Bool
== a
t then c
1 else c
101)
  | a
z forall a. Eq a => a -> a -> Bool
/= a
u Bool -> Bool -> Bool
&& a
z forall a. Eq a => a -> a -> Bool
/= a
t Bool -> Bool -> Bool
&& a
t forall a. Ord a => a -> a -> Bool
>= a
0 = (a
t, a
u, c
n forall a. Num a => a -> a -> a
+ c
1)
  | Bool
otherwise = (-a
1, a
u, c
n)

-- | Being given the data satisfying the constraints in the module header checks whether in the
-- 'Array' the distance between positions of the first two arguments values is equal to the unsigned 
-- third argument. The following is true: if 'unsafeSignDistanceIJ' @i@ @j@ @d@ @array@ == 'True' then
-- 'unsafeUnsignDistanceIJ' @i@ @j@ @d@ @array@ == 'True', but not necessarily vice versa. 
unsafeUnsignDistanceIJ 
  :: Int 
  -> Int 
  -> Int -- ^ Only for positive values can give 'True', if the distance between the positions of the elements equal to the first two arguments are equal to this argument. Otherwise, 'False'.
  -> Array Int Int 
  -> Bool
unsafeUnsignDistanceIJ :: Int -> Int -> Int -> Array Int Int -> Bool
unsafeUnsignDistanceIJ Int
i Int
j Int
d = (\(Int
_,Int
_,Int
r) -> Int
r forall a. Eq a => a -> a -> Bool
== Int
d) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a b.
Foldable t =>
(a -> b -> b) -> b -> t a -> b
foldr forall {c} {a}.
(Ord c, Ord a, Num c, Num a) =>
a -> (a, a, c) -> (a, a, c)
helpG3 (Int
j, Int
i, -Int
1)

helpG3 :: a -> (a, a, c) -> (a, a, c)
helpG3 a
z (a
t, a
u, c
n)
  | c
n forall a. Ord a => a -> a -> Bool
< c
0 = if (a
z forall a. Eq a => a -> a -> Bool
/= a
t Bool -> Bool -> Bool
&& a
z forall a. Eq a => a -> a -> Bool
/= a
u) then (a
t, a
u, c
n) else (a
t, a
u, c
1)
  | a
z forall a. Eq a => a -> a -> Bool
/= a
u Bool -> Bool -> Bool
&& a
z forall a. Eq a => a -> a -> Bool
/= a
t Bool -> Bool -> Bool
&& a
t forall a. Ord a => a -> a -> Bool
>= a
0 = (a
t, a
u, c
n forall a. Num a => a -> a -> a
+ c
1)
  | Bool
otherwise = (-a
1, a
u, c
n)

-- | 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 :: forall (t :: * -> *).
(InsertLeft t (Array Int Int), Monoid (t (Array Int Int))) =>
Int -> Int -> t (Array Int Int) -> t (Array Int Int)
filterOrderIJ Int
i Int
j = 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 returns the elements that satisfy 'unsafeSignDistanceIJ' as a predicate.
filterSignDistanceIJ :: (InsertLeft t (Array Int Int), Monoid (t (Array Int Int))) => Int -> Int -> Int -> t (Array Int Int) -> t (Array Int Int)
filterSignDistanceIJ :: forall (t :: * -> *).
(InsertLeft t (Array Int Int), Monoid (t (Array Int Int))) =>
Int -> Int -> Int -> t (Array Int Int) -> t (Array Int Int)
filterSignDistanceIJ Int
i Int
j Int
d = forall (t :: * -> *) a.
(InsertLeft t a, Monoid (t a)) =>
(a -> Bool) -> t a -> t a
filterG (Int -> Int -> Int -> Array Int Int -> Bool
unsafeSignDistanceIJ Int
i Int
j Int
d)

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

-- | Being given the data satisfying the constraints in the module header returns the elements that pairwisely (1 and 2, 2 and 3) satisfy 'unsafeSignDistanceIJ' as a predicate.
filterSignDistanceIJK3 :: (InsertLeft t (Array Int Int), Monoid (t (Array Int Int))) => Int -> Int -> Int -> Int -> Int -> t (Array Int Int) -> t (Array Int Int)
filterSignDistanceIJK3 :: forall (t :: * -> *).
(InsertLeft t (Array Int Int), Monoid (t (Array Int Int))) =>
Int
-> Int
-> Int
-> Int
-> Int
-> t (Array Int Int)
-> t (Array Int Int)
filterSignDistanceIJK3 Int
i Int
j Int
k Int
d1 Int
d2 = forall (t :: * -> *) a.
(InsertLeft t a, Monoid (t a)) =>
(a -> Bool) -> t a -> t a
filterG (\Array Int Int
arr -> Int -> Int -> Int -> Array Int Int -> Bool
unsafeSignDistanceIJ Int
i Int
j Int
d1 Array Int Int
arr Bool -> Bool -> Bool
&& Int -> Int -> Int -> Array Int Int -> Bool
unsafeSignDistanceIJ Int
j Int
k Int
d2 Array Int Int
arr)

-- | Being given the data satisfying the constraints in the module header returns the elements that pairwisely (1 and 2, 2 and 3) satisfy 'unsafeUnsignDistanceIJ' as a predicate.
filterUnsignDistanceIJK3 :: (InsertLeft t (Array Int Int), Monoid (t (Array Int Int))) => Int -> Int -> Int -> Int -> Int -> t (Array Int Int) -> t (Array Int Int)
filterUnsignDistanceIJK3 :: forall (t :: * -> *).
(InsertLeft t (Array Int Int), Monoid (t (Array Int Int))) =>
Int
-> Int
-> Int
-> Int
-> Int
-> t (Array Int Int)
-> t (Array Int Int)
filterUnsignDistanceIJK3 Int
i Int
j Int
k Int
d1 Int
d2 = forall (t :: * -> *) a.
(InsertLeft t a, Monoid (t a)) =>
(a -> Bool) -> t a -> t a
filterG (\Array Int Int
arr -> Int -> Int -> Int -> Array Int Int -> Bool
unsafeUnsignDistanceIJ Int
i Int
j Int
d1 Array Int Int
arr Bool -> Bool -> Bool
&& Int -> Int -> Int -> Array Int Int -> Bool
unsafeUnsignDistanceIJ Int
j Int
k Int
d2 Array Int Int
arr)

-- | Being given the data satisfying the constraints in the module header returns the elements that satisfy both 'unsafeSignDistanceIJ' with the 1st, 2nd and 4th arguments and 'unsafeUnsignDistanceIJ' with the 2nd, 3rd and 5th arguments as predicates.
filterMixedDistanceIJK3 :: (InsertLeft t (Array Int Int), Monoid (t (Array Int Int))) => Int -> Int -> Int -> Int -> Int -> t (Array Int Int) -> t (Array Int Int)
filterMixedDistanceIJK3 :: forall (t :: * -> *).
(InsertLeft t (Array Int Int), Monoid (t (Array Int Int))) =>
Int
-> Int
-> Int
-> Int
-> Int
-> t (Array Int Int)
-> t (Array Int Int)
filterMixedDistanceIJK3 Int
i Int
j Int
k Int
d1 Int
d2 = forall (t :: * -> *) a.
(InsertLeft t a, Monoid (t a)) =>
(a -> Bool) -> t a -> t a
filterG (\Array Int Int
arr -> Int -> Int -> Int -> Array Int Int -> Bool
unsafeSignDistanceIJ Int
i Int
j Int
d1 Array Int Int
arr Bool -> Bool -> Bool
&& Int -> Int -> Int -> Array Int Int -> Bool
unsafeUnsignDistanceIJ Int
j Int
k Int
d2 Array Int Int
arr)

-- | 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 :: forall (t :: * -> *).
(InsertLeft t (Array Int Int), Monoid (t (Array Int Int))) =>
Int -> Int -> Int -> t (Array Int Int) -> t (Array Int Int)
unsafeTriples Int
i Int
j Int
k = 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 :: forall (t :: * -> *).
(InsertLeft t (Array Int Int), Monoid (t (Array Int Int))) =>
Int -> Int -> Int -> Int -> t (Array Int Int) -> t (Array Int Int)
unsafeQuadruples Int
i Int
j Int
k Int
l = 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 :: forall (t :: * -> *).
(InsertLeft t (Array Int Int), Monoid (t (Array Int Int))) =>
Int -> Array Int Int -> t (Array Int Int) -> t (Array Int Int)
unsafeSeveralA !Int
i0 Array Int Int
arr t (Array Int Int)
x = forall (t :: * -> *) a.
(InsertLeft t a, Monoid (t a)) =>
(a -> Bool) -> t a -> t a
filterG (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 = 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 :: forall (t :: * -> *).
(InsertLeft t (Array Int Int), Monoid (t (Array Int Int))) =>
Int -> Array Int Int -> t (Array Int Int) -> t (Array Int Int)
unsafeSeveralB !Int
i0 Array Int Int
arr t (Array Int Int)
x = forall (t :: * -> *) a.
(InsertLeft t a, Monoid (t a)) =>
(a -> Bool) -> t a -> t a
filterG (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 = 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 :: forall (t :: * -> *).
(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)
arr t (Array Int Int)
xs = forall (t :: * -> *) a.
(InsertLeft t a, Monoid (t a)) =>
(a -> Bool) -> t a -> t a
filterG (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 = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (\(Int
k,a
j) -> forall i e. Array i e -> Int -> e
unsafeAt Array i a
arr2 Int
k 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 :: forall (t :: * -> *).
(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
arr t (Array Int Int)
xs = forall (t :: * -> *) a.
(InsertLeft t a, Monoid (t a)) =>
(a -> Bool) -> t a -> t a
filterG (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 = forall (t :: * -> *) a. Foldable t => (a -> Bool) -> t a -> Bool
all (\Int
k -> forall i e. Array i e -> Int -> e
unsafeAt Array i Int
arr2 Int
k forall a. Eq a => a -> a -> Bool
== Int
k) t Int
arr1