{-# LANGUAGE BangPatterns, FlexibleInstances, MultiParamTypeClasses #-}
module String.Languages.UniquenessPeriods.Vector where
import qualified Data.Vector as V
data UniquenessGeneral1 a b = UG1 a [b] (V.Vector b) | UG2 a [b] (V.Vector b) deriving Eq
class UniquenessGeneral a b where
get :: a -> b
type UniquenessGeneral2 a = V.Vector ([Int], a)
instance (Eq a) => UniquenessGeneral (UniquenessGeneral1 Bool a) (UniquenessGeneral2 a) where
get (UG1 y whspss v) = uniquenessPeriodsVector1 y whspss v
get (UG2 y whspss v) = uniquenessPeriodsVector2 y whspss v
uniquenessPeriodsVector1 :: Eq a => Bool -> [a] -> V.Vector a -> UniquenessGeneral2 a
uniquenessPeriodsVector1 y whspss v
| V.null v = V.empty
| otherwise = let !v1 = V.force . V.indexed $ v in
let f !x = if V.null x then Nothing
else Just . (\(v2,v3) -> ((V.toList . V.map fst $ v2,snd . V.unsafeIndex v2 $ 0),v3)) .
V.partition (\(_,xs) -> xs == (snd . V.unsafeIndex x $ 0)) $ x in
V.force . (if y then V.filter (\(_,!zs) -> zs `notElem` whspss) else id) . V.unfoldr f $ v1
uniquenessPeriodsVector2 :: Eq a => Bool -> [a] -> V.Vector a -> UniquenessGeneral2 a
uniquenessPeriodsVector2 y whspss v
| V.null v = V.empty
| otherwise = let !v1 = V.force . V.indexed $ v in
let f !x = if V.null x then Nothing
else Just . (\(v2,v3) -> ((V.toList . (\v4 -> V.zipWith subtract v4 (V.unsafeSlice 1 (V.length v4 -1) v4)) . V.map fst $ v2,snd .
V.unsafeIndex v2 $ 0),v3)) . V.partition (\(_,xs) -> xs == (snd . V.unsafeIndex x $ 0)) $ x in
V.force . (if y then V.filter (\(ys,!zs) -> not (null ys) && zs `notElem` whspss) else id) . V.unfoldr f $ v1