-- |
-- 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.



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

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

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

-- | The second norm for the list of positive 'Int'. For not empty lists equals to the sum of the elements.
norm2 :: [Int] -> Int
norm2 xs = sum xs

-- | The third norm for the list of positive '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

-- | The fourth norm for the list of positive '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])

-- | The fifth norm for the list of positive '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
 | otherwise = sum xs `quot` (minimum xs + minimum (xs \\ [minimum xs]))

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