{-# LANGUAGE BangPatterns          #-}
{-# LANGUAGE FlexibleContexts      #-}
{-# LANGUAGE FlexibleInstances     #-}
{-# LANGUAGE InstanceSigs          #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE OverloadedStrings     #-}
{-# LANGUAGE ScopedTypeVariables   #-}
{-# LANGUAGE TypeFamilies          #-}

module HaskellWorks.Data.Json.Internal.PartialIndex where

import Control.Arrow
import Control.Monad
import Data.String
import HaskellWorks.Data.Bits.BitWise
import HaskellWorks.Data.Drop
import HaskellWorks.Data.Json.Internal.CharLike
import HaskellWorks.Data.Json.Standard.Cursor.Generic
import HaskellWorks.Data.Positioning
import HaskellWorks.Data.RankSelect.Base.Rank0
import HaskellWorks.Data.RankSelect.Base.Rank1
import HaskellWorks.Data.RankSelect.Base.Select1
import HaskellWorks.Data.TreeCursor
import HaskellWorks.Data.Uncons
import Prelude                                        hiding (drop)

import qualified Data.ByteString                  as BS
import qualified Data.List                        as L
import qualified HaskellWorks.Data.BalancedParens as BP

data JsonPartialIndex
  = JsonPartialIndexString BS.ByteString
  | JsonPartialIndexNumber BS.ByteString
  | JsonPartialIndexObject [(BS.ByteString, JsonPartialIndex)]
  | JsonPartialIndexArray [JsonPartialIndex]
  | JsonPartialIndexBool Bool
  | JsonPartialIndexNull
  | JsonPartialIndexError String
  deriving (JsonPartialIndex -> JsonPartialIndex -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: JsonPartialIndex -> JsonPartialIndex -> Bool
$c/= :: JsonPartialIndex -> JsonPartialIndex -> Bool
== :: JsonPartialIndex -> JsonPartialIndex -> Bool
$c== :: JsonPartialIndex -> JsonPartialIndex -> Bool
Eq, Int -> JsonPartialIndex -> ShowS
[JsonPartialIndex] -> ShowS
JsonPartialIndex -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [JsonPartialIndex] -> ShowS
$cshowList :: [JsonPartialIndex] -> ShowS
show :: JsonPartialIndex -> String
$cshow :: JsonPartialIndex -> String
showsPrec :: Int -> JsonPartialIndex -> ShowS
$cshowsPrec :: Int -> JsonPartialIndex -> ShowS
Show)

class JsonPartialIndexAt a where
  jsonPartialIndexAt :: a -> JsonPartialIndex

instance (BP.BalancedParens w, Rank0 w, Rank1 w, Select1 v, TestBit w) => JsonPartialIndexAt (GenericCursor BS.ByteString v w) where
  jsonPartialIndexAt :: GenericCursor ByteString v w -> JsonPartialIndex
jsonPartialIndexAt GenericCursor ByteString v w
k = case forall v. Uncons v => v -> Maybe (Elem v, v)
uncons ByteString
remainder of
    Just (!Elem ByteString
c, ByteString
_) | forall c. JsonCharLike c => c -> Bool
isLeadingDigit2 Elem ByteString
c -> ByteString -> JsonPartialIndex
JsonPartialIndexNumber  ByteString
remainder
    Just (!Elem ByteString
c, ByteString
_) | forall c. JsonCharLike c => c -> Bool
isQuotDbl Elem ByteString
c       -> ByteString -> JsonPartialIndex
JsonPartialIndexString  ByteString
remainder
    Just (!Elem ByteString
c, ByteString
_) | forall c. JsonCharLike c => c -> Bool
isChar_t Elem ByteString
c        -> Bool -> JsonPartialIndex
JsonPartialIndexBool    Bool
True
    Just (!Elem ByteString
c, ByteString
_) | forall c. JsonCharLike c => c -> Bool
isChar_f Elem ByteString
c        -> Bool -> JsonPartialIndex
JsonPartialIndexBool    Bool
False
    Just (!Elem ByteString
c, ByteString
_) | forall c. JsonCharLike c => c -> Bool
isChar_n Elem ByteString
c        -> JsonPartialIndex
JsonPartialIndexNull
    Just (!Elem ByteString
c, ByteString
_) | forall c. JsonCharLike c => c -> Bool
isBraceLeft Elem ByteString
c     -> [(ByteString, JsonPartialIndex)] -> JsonPartialIndex
JsonPartialIndexObject (Maybe (GenericCursor ByteString v w)
-> [(ByteString, JsonPartialIndex)]
mapValuesFrom   (forall k. TreeCursor k => k -> Maybe k
firstChild GenericCursor ByteString v w
k))
    Just (!Elem ByteString
c, ByteString
_) | forall c. JsonCharLike c => c -> Bool
isBracketLeft Elem ByteString
c   -> [JsonPartialIndex] -> JsonPartialIndex
JsonPartialIndexArray  (Maybe (GenericCursor ByteString v w) -> [JsonPartialIndex]
arrayValuesFrom (forall k. TreeCursor k => k -> Maybe k
firstChild GenericCursor ByteString v w
k))
    Just (Elem ByteString, ByteString)
_                           -> String -> JsonPartialIndex
JsonPartialIndexError String
"Invalid Json Type"
    Maybe (Elem ByteString, ByteString)
Nothing                          -> String -> JsonPartialIndex
JsonPartialIndexError String
"End of data"
    where ik :: v
ik                = forall t v w. GenericCursor t v w -> v
interests GenericCursor ByteString v w
k
          bpk :: w
bpk               = forall t v w. GenericCursor t v w -> w
balancedParens GenericCursor ByteString v w
k
          p :: Position
p                 = Count -> Position
lastPositionOf (forall v. Select1 v => v -> Count -> Count
select1 v
ik (forall v. Rank1 v => v -> Count -> Count
rank1 w
bpk (forall t v w. GenericCursor t v w -> Count
cursorRank GenericCursor ByteString v w
k)))
          remainder :: ByteString
remainder         = forall v. Drop v => Count -> v -> v
drop (forall a. ToCount a => a -> Count
toCount Position
p) (forall t v w. GenericCursor t v w -> t
cursorText GenericCursor ByteString v w
k)
          arrayValuesFrom :: Maybe (GenericCursor BS.ByteString v w) -> [JsonPartialIndex]
          arrayValuesFrom :: Maybe (GenericCursor ByteString v w) -> [JsonPartialIndex]
arrayValuesFrom = forall b a. (b -> Maybe (a, b)) -> b -> [a]
L.unfoldr (forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a. JsonPartialIndexAt a => a -> JsonPartialIndex
jsonPartialIndexAt forall (a :: * -> * -> *) b c c'.
Arrow a =>
a b c -> a b c' -> a b (c, c')
&&& forall k. TreeCursor k => k -> Maybe k
nextSibling))
          mapValuesFrom :: Maybe (GenericCursor ByteString v w)
-> [(ByteString, JsonPartialIndex)]
mapValuesFrom Maybe (GenericCursor ByteString v w)
j   = forall {b}. [b] -> [(b, b)]
pairwise (Maybe (GenericCursor ByteString v w) -> [JsonPartialIndex]
arrayValuesFrom Maybe (GenericCursor ByteString v w)
j) forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= forall {b}. (JsonPartialIndex, b) -> [(ByteString, b)]
asField
          pairwise :: [b] -> [(b, b)]
pairwise (b
a:b
b:[b]
rs) = (b
a, b
b) forall a. a -> [a] -> [a]
: [b] -> [(b, b)]
pairwise [b]
rs
          pairwise [b]
_        = []
          asField :: (JsonPartialIndex, b) -> [(ByteString, b)]
asField (JsonPartialIndex
a, b
b)    = case JsonPartialIndex
a of
                                JsonPartialIndexString ByteString
s -> [(ByteString
s, b
b)]
                                JsonPartialIndex
_                        -> []