{-# OPTIONS_HADDOCK show-extensions #-} -- | -- Module : Languages.UniquenessPeriods.Array.Constraints -- Copyright : (c) OleksandrZhabenko 2020 -- 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 ) 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 i j = (\(_,_,r) -> if r == 0 then True else False) . foldl' helpG (i,j,0) helpG (t,u,n) z | z == t = (t,u,1) | z == u = case n of 0 -> (t,u,2) _ -> (t,u,n - 1) | otherwise = (t,u,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 i j = filterG (unsafeOrderIJ i 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 i j k = filterG (\v -> unsafeOrderIJ i j v && unsafeOrderIJ j k 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 i j k l = filterG (\v -> unsafeOrderIJ i j v && unsafeOrderIJ j k v && unsafeOrderIJ k l 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 computtions) 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 !i0 arr x = filterG (g i0 arr) x where g !i0 !arr1 arr2 = all id . amap (\k -> unsafeOrderIJ i0 k arr2) $ 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 computtions) 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 !i0 arr x = filterG (g i0 arr) x where g !i0 !arr1 arr2 = all id . amap (\k -> unsafeOrderIJ k i0 arr2) $ arr1