module HaskellWorks.Data.BalancedParens.Internal.Broadword.FindUnmatchedCloseFar.Vector32
  ( findUnmatchedCloseFar
  ) where

import Data.Int
import Data.Word
import HaskellWorks.Data.AtIndex
import HaskellWorks.Data.Bits.BitLength
import HaskellWorks.Data.Int.Unsigned
import HaskellWorks.Data.Positioning

import qualified Data.Vector.Storable                                                             as DVS
import qualified HaskellWorks.Data.BalancedParens.Internal.Broadword.FindUnmatchedCloseFar.Word32 as BWW32
import qualified HaskellWorks.Data.Drop                                                           as HW
import qualified HaskellWorks.Data.Length                                                         as HW

findUnmatchedCloseCont :: Int64 -> Count -> DVS.Vector Word32 -> Count
findUnmatchedCloseCont :: Int64 -> Count -> Vector Word32 -> Count
findUnmatchedCloseCont Int64
i Count
c Vector Word32
v = if Int64
i Int64 -> Int64 -> Bool
forall a. Ord a => a -> a -> Bool
< Vector Word32 -> Int64
forall v. Length v => v -> Int64
HW.end Vector Word32
v
  then case Count -> Count -> Word32 -> Count
BWW32.findUnmatchedCloseFar Count
c Count
0 Word32
w of
    Count
q -> if Count
q Count -> Count -> Bool
forall a. Ord a => a -> a -> Bool
>= Word32 -> Count
forall v. BitLength v => v -> Count
bitLength Word32
w
      then Int64 -> Count -> Vector Word32 -> Count
findUnmatchedCloseCont (Int64
i Int64 -> Int64 -> Int64
forall a. Num a => a -> a -> a
+ Int64
1) (Count
q Count -> Count -> Count
forall a. Num a => a -> a -> a
- Word32 -> Count
forall v. BitLength v => v -> Count
bitLength Word32
w) Vector Word32
v
      else Count
b Count -> Count -> Count
forall a. Num a => a -> a -> a
+ Count
q
  else Count
b Count -> Count -> Count
forall a. Num a => a -> a -> a
+ Count
c
  where b :: Count
b  = Int64 -> UnsignedOf Int64
forall a. Unsigned a => a -> UnsignedOf a
unsigned Int64
i Count -> Count -> Count
forall a. Num a => a -> a -> a
* Word32 -> Count
forall v. BitLength v => v -> Count
bitLength Word32
w -- base
        w :: Elem (Vector Word32)
w  = Vector Word32
v Vector Word32 -> Int64 -> Elem (Vector Word32)
forall v. AtIndex v => v -> Int64 -> Elem v
!!! Int64 -> Int64
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int64
i
{-# INLINE findUnmatchedCloseCont #-}

findUnmatchedClose' :: Word64 -> Word64 -> DVS.Vector Word32 -> Count
findUnmatchedClose' :: Count -> Count -> Vector Word32 -> Count
findUnmatchedClose' Count
c Count
p Vector Word32
v = if Vector Word32 -> Int
forall a. Storable a => Vector a -> Int
DVS.length Vector Word32
v Int -> Int -> Bool
forall a. Ord a => a -> a -> Bool
> Int
0
    then case Count -> Count -> Word32 -> Count
BWW32.findUnmatchedCloseFar Count
c Count
p Word32
w of
        Count
q -> if Count
q Count -> Count -> Bool
forall a. Ord a => a -> a -> Bool
>= Word32 -> Count
forall v. BitLength v => v -> Count
bitLength Word32
w
          then Int64 -> Count -> Vector Word32 -> Count
findUnmatchedCloseCont Int64
1 (Count
q Count -> Count -> Count
forall a. Num a => a -> a -> a
- Word32 -> Count
forall v. BitLength v => v -> Count
bitLength Word32
w) Vector Word32
v
          else Count
q
    else Count
p Count -> Count -> Count
forall a. Num a => a -> a -> a
* Count
2 Count -> Count -> Count
forall a. Num a => a -> a -> a
+ Count
c
  where w :: Elem (Vector Word32)
w  = Vector Word32
v Vector Word32 -> Int64 -> Elem (Vector Word32)
forall v. AtIndex v => v -> Int64 -> Elem v
!!! Int64
0
{-# INLINE findUnmatchedClose' #-}

findUnmatchedCloseFar :: Word64 -> Word64 -> DVS.Vector Word32 -> Count
findUnmatchedCloseFar :: Count -> Count -> Vector Word32 -> Count
findUnmatchedCloseFar Count
c Count
p Vector Word32
v = Count -> Count -> Vector Word32 -> Count
findUnmatchedClose' Count
c (Count
p Count -> Count -> Count
forall a. Num a => a -> a -> a
- Count
vd) (Count -> Vector Word32 -> Vector Word32
forall v. Drop v => Count -> v -> v
HW.drop Count
vi Vector Word32
v) Count -> Count -> Count
forall a. Num a => a -> a -> a
+ Count
vd
  where vi :: Count
vi = Count
p Count -> Count -> Count
forall a. Integral a => a -> a -> a
`div` Vector Word32 -> Count
forall v. (AtIndex v, BitLength (Elem v)) => v -> Count
elemBitLength Vector Word32
v
        vd :: Count
vd = Count
vi Count -> Count -> Count
forall a. Num a => a -> a -> a
* Vector Word32 -> Count
forall v. (AtIndex v, BitLength (Elem v)) => v -> Count
elemBitLength Vector Word32
v
{-# INLINE findUnmatchedCloseFar #-}