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

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

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