module Data.List.Alternating(
    Alternating(..)
  , withNeighbours
  , mergeAlternating
  , insertBreakPoints
  , reverse
  ) where
import Prelude hiding (reverse)
import Control.Lens
import Data.Bifoldable
import Data.Bitraversable
import Data.Ext
import qualified Data.List as List
data Alternating a b = Alternating a [b :+ a] deriving (Show,Eq,Ord)
instance Bifunctor Alternating where
  bimap = bimapDefault
instance Bifoldable Alternating where
  bifoldMap = bifoldMapDefault
instance Bitraversable Alternating where
  bitraverse f g (Alternating a xs) = Alternating <$> f a <*> traverse (bitraverse g f) xs
withNeighbours                     :: Alternating a b -> [(a,b :+ a)]
withNeighbours (Alternating a0 xs) = let as = a0 : map (^.extra) xs
                                     in zipWith (\a ba -> (a,ba)) as xs
mergeAlternating                         :: Ord t
                                         => (t -> a -> b -> c)
                                         -> Alternating a t -> Alternating b t -> [t :+ c]
mergeAlternating f (Alternating a00 as0)
                   (Alternating b00 bs0) = go a00 b00 as0 bs0
  where
    go a  _  []                bs                 = map (\(t :+ b) -> t :+ f t a b) bs
    go _  b  as                []                 = map (\(t :+ a) -> t :+ f t a b) as
    go a0 b0 as@((t :+ a):as') bs@((t' :+ b):bs') = case t `compare` t' of
                                                      LT -> (t  :+ f t  a  b0) : go a  b0 as' bs
                                                      EQ -> (t  :+ f t  a  b)  : go a  b  as' bs'
                                                      GT -> (t' :+ f t' a0 b)  : go a0 b  as  bs'
insertBreakPoints                         :: Ord t => [t] -> Alternating a t -> Alternating a t
insertBreakPoints ts a@(Alternating a0 _) =
  Alternating a0 $ mergeAlternating (\_ _ a' -> a') (Alternating undefined (ext <$> ts)) a
reverse                      :: Alternating a b -> Alternating a b
reverse p@(Alternating s xs) = case xs of
    []             -> p
    ((e1 :+ _):tl) -> let ys = (e1 :+ s) : List.zipWith (\(_ :+ v) (e :+ _) -> e :+ v) xs tl
                          t  = (last xs)^.extra
                      in Alternating t (List.reverse ys)