-- |
-- Module      :  DobutokO.Poetry.Norms
-- Copyright   :  (c) OleksandrZhabenko 2020
-- License     :  MIT
-- Stability   :  Experimental
-- Maintainer  :  olexandr543@yahoo.com
--
-- Helps to order the 7 or less Ukrainian words (or their concatenations) 
-- to obtain (to some extent) suitable for poetry or music text. This module 
-- provides several different norms that allow to research the text and 
-- to create interesting sequences.

module DobutokO.Poetry.Norms (
  -- * Different norms
  norm1
  , norm2
  , norm3
  , norm4
  , norm5
  , norm51
  , norm513
  , norm6
  , splitNorm
) where

import qualified Data.Vector as V
import Data.List ((\\))

-- | The first norm for the list of non-negative 'Int'. For not empty lists equals to the maximum element.
norm1 :: [Int] -> Int
norm1 xs
  | null xs = 0
  | otherwise = maximum xs
{-# INLINE norm1 #-}

-- | The second norm for the list of non-negative 'Int'. For not empty lists equals to the sum of the elements.
norm2 :: [Int] -> Int
norm2 xs = sum xs
{-# INLINE norm2 #-}

-- | The third norm for the list of non-negative 'Int'. For not empty lists equals to the sum of the doubled maximum element and the rest elements of the list.
norm3 :: [Int] -> Int
norm3 xs
 | null xs = 0
 | otherwise = maximum xs + sum xs
{-# INLINE norm3 #-}

-- | The fourth norm for the list of non-negative 'Int'. Equals to the sum of the 'norm3' and 'norm2'.
norm4 :: [Int] -> Int
norm4 xs
 | null xs = 0
 | otherwise = maximum xs + sum xs + maximum (xs \\ [maximum xs])
{-# INLINE norm4 #-}

-- | The fifth norm for the list of non-negative 'Int'. For not empty lists equals to the sum of the elements quoted with sum of the two most minimum elements.
norm5 :: [Int] -> Int
norm5 xs
 | null xs = 0
 | minimum xs == 0 = norm5 . filter (/= 0) $ xs
 | otherwise = sum xs `quot` (minimum xs + minimum (xs \\ [minimum xs]))
{-# INLINE norm5 #-}

-- | The fifth modified norm for the list of non-negative 'Int'. Tries to take into account doubled and prolonged sounds to reduce their influence on the 'norm5'.
norm51 :: [Int] -> Int
norm51 xs
 | null xs = 0
 | compare (minimum xs) 1 /= GT = let ys = filter (\t -> compare t 1 == GT) xs in (3 * sum xs) `quot` (minimum ys + minimum (ys \\ [minimum ys]))
 | otherwise = (3 * sum xs) `quot` (minimum xs + minimum (xs \\ [minimum xs]))
{-# INLINE norm51 #-}

-- | The fifth modified (with three minimums) norm for the list of non-negative 'Int'. Tries to take into account doubled and prolonged sounds 
-- to reduce their influence on the 'norm5'.
norm513 :: [Int] -> Int
norm513 xs
 | null xs = 0
 | compare (minimum xs) 1 /= GT =
   let ys = filter (\t -> compare t 1 == GT) xs
       zs = ys \\ [minimum ys] in (3 * sum xs) `quot` (minimum ys + minimum zs + minimum (zs \\ [minimum zs]))
 | otherwise =
   let zs = xs \\ [minimum xs] in (3 * sum xs) `quot` (minimum xs + minimum zs + minimum (zs \\ [minimum zs]))
{-# INLINE norm513 #-}

-- | The sixth norm for the list of non-negative 'Int'.
norm6 :: [Int] -> Int
norm6 xs = floor (fromIntegral (norm5 xs * sum xs) / fromIntegral (norm3 xs))
{-# INLINE norm6 #-}

-- | Splits a given list of non-negative integers into lists of elements not equal to zero and then applies to them the norms from the 'V.Vector' starting 
-- from the last element in the vector right-to-left.
splitNorm :: [Int] -> V.Vector ([Int] -> Int) -> [Int]
splitNorm xs vN
 | null (filter (/=0) xs) || V.length vN /= length (filter (== 0) xs) + 1 = []
 | otherwise =
    let (ys,zs) = break (== 0) xs
        zzs = drop 1 zs
        in (V.unsafeIndex vN (V.length vN - 1)) ys:splitNorm zzs (V.unsafeSlice 0 (V.length vN - 1) vN)