{-# LANGUAGE
    PatternGuards #-}
-- | Extract substructures from JSON structures by following a path.
module Text.JSONb.Path(
  -- * Building selectors
    Selector
  , key
  , idx

  -- * Building paths
  , Path(..)

  -- * Using paths
  , get
  , getOne) where

import Data.Maybe
import qualified Data.Trie            as T
import qualified Text.JSONb           as J
import qualified Data.ByteString      as B
import qualified Data.ByteString.UTF8 as U8

-- | Selects an element from a collection. Abstract.
data Selector
  = Key B.ByteString
  | Idx Int

-- | Select from an @Object@ by key.
key :: String -> Selector
key = Key . U8.fromString

-- | Select from an @Array@ by index.
idx :: Int -> Selector
idx = Idx

infixr 7 :=>

-- | A @'Path'@ is used to traverse a @JSON@ structure and yield
-- zero or more substructures.
data Path
  = Fail               -- ^ Yield nothing.
  | Yield              -- ^ Yield this structure.
  | Selector :=> Path  -- ^ Select an element and continue on some path.
  | All Path           -- ^ Follow a path for each @Array@ element.

  | Compute (J.JSON -> Path) -- ^ Choose a path programmatically.

-- | Follow a path to get all matching substructures.
get :: Path -> J.JSON -> [J.JSON]

get Fail  _ = []
get Yield x = [x]

get (Key k :=> p) (J.Object t) | Just x <- T.lookup k t = get p x
get (Key _ :=> _) _ = []

get (Idx i :=> p) (J.Array xs) | (_, (y:_)) <- splitAt i xs = get p y
get (Idx _ :=> _) _ = []

get (All p) (J.Array xs) = concatMap (get p) xs
get (All _) _ = []

get (Compute f) j = get (f j) j

-- | Follow a path to get the first matching substructure.
getOne :: Path -> J.JSON -> Maybe J.JSON
getOne p = listToMaybe . get p