-- |
-- Module      :  Languages.UniquenessPeriods.Vector.Data
-- Copyright   :  (c) OleksandrZhabenko 2020
-- License     :  MIT
-- Stability   :  Experimental
-- Maintainer  :  olexandr543@yahoo.com
--
-- Is a generalization of the DobutokO.Poetry.Data module 
-- functionality from the @dobutokO-poetry-general@ package. 
-- 

{-# LANGUAGE FlexibleInstances, MultiParamTypeClasses #-}

module Languages.UniquenessPeriods.Vector.Data where

import Data.Maybe (fromJust)
import qualified Data.Vector as V
import Languages.UniquenessPeriods.Vector.Auxiliary (lastFrom3)

type UniquenessG1 a b = ([b],V.Vector b,[a])

-- | The list in the 'PA' variant represent the prepending @[a]@ and the postpending one respectively. 'K' constuctor actually means no prepending and 
-- postpending (usually of the text). Are used basically to control the behaviour of the functions.
data PreApp a = K | PA [a] [a] deriving Eq

class UGG1 a b where
  get1m :: a -> [b]
  get2m :: a -> [b]
  getm :: Bool -> a -> [b]
  getm True = get1m
  getm _ = get2m
  preapp :: a -> [[b]] -> [[b]]
  setm :: [b] -> [b] -> a

instance Eq a => UGG1 (PreApp a) a where
  get1m K = []
  get1m (PA xs _) = xs
  get2m K = []
  get2m (PA _ ys) = ys
  preapp K xss = xss
  preapp (PA xs ys) yss = xs:yss ++ [ys]
  setm [] [] = K
  setm xs ys = PA xs ys

type Preapp a = PreApp a

isPA :: PreApp a -> Bool
isPA K = False
isPA _ = True

isK :: PreApp a -> Bool
isK K = True
isK _ = False

-- | Is used to control whether to return data or only to print the needed information. The 'U' contstuctor corresponds to the information printing and 'UL' to 
-- returning also data. The last one so can be further used.
data UniquenessG a b = U b | UL ([a],b) deriving Eq

instance (Show a, Show b) => Show (UniquenessG a (V.Vector (UniquenessG1 a b))) where
  show (U v) = show . V.map lastFrom3 $ v
  show (UL (wss,_)) = show wss

type UniqG a b = UniquenessG [a] (V.Vector (UniquenessG1 a b))

-- | Decomposes the data type 'UniqG' into its components. The inverse to the 'set2'.
get2 :: UniqG a b -> (Maybe [[a]], V.Vector (UniquenessG1 a b))
get2 (U v) = (Nothing,v)
get2 (UL (wss,v)) = (Just wss,v)

-- | Compose the data type 'UniqG' from its components. The inverse to the 'get2'.
set2 :: (Maybe [[a]], V.Vector (UniquenessG1 a b)) -> UniqG a b
set2 (Just wss, v) = UL (wss,v)
set2 (Nothing, v) = U v

isU :: UniqG a b -> Bool
isU (U _) = True
isU _ = False

isUL :: UniqG a b -> Bool
isUL (UL _) = True
isUL _ = False