module JSONPointer where
import Control.Monad (when)
import Data.Aeson
import qualified Data.Hashable as HA
import qualified Data.HashMap.Strict as HM
import Data.Semigroup (Semigroup)
import Data.Text (Text)
import qualified Data.Text as T
import qualified Data.Vector as V
import GHC.Generics (Generic)
import Test.QuickCheck
import Text.Read (readMaybe)
import Control.Applicative
import Data.Monoid
import Data.Traversable
data ResolutionError
= ObjectLookupFailed
| ArrayIndexInvalid
| ArrayElemNotFound
| ExpectedObjectOrArray
deriving (Eq, Show)
resolve :: Pointer -> Value -> Either ResolutionError Value
resolve (Pointer []) v = Right v
resolve (Pointer (t:ts)) v = resolveToken t v >>= resolve (Pointer ts)
newtype Pointer
= Pointer { _unPointer :: [Token] }
deriving (Eq, Show, Semigroup, Monoid, Generic, Arbitrary)
instance HA.Hashable Pointer
instance FromJSON Pointer where
parseJSON = withText "JSON Pointer" $ \t ->
case unescape t of
Left e -> fail (show e)
Right p -> pure p
instance ToJSON Pointer where
toJSON = String . escape
newtype Token
= Token { _unToken :: Text }
deriving (Eq, Show, Generic)
instance HA.Hashable Token
instance Arbitrary Token where
arbitrary = Token . T.pack <$> arbitrary
escape :: Pointer -> Text
escape (Pointer []) = ""
escape (Pointer ts) =
T.cons '/'
. T.intercalate "/"
. fmap (T.replace "/" "~1" . T.replace "~" "~0" . _unToken)
$ ts
data FormatError
= InvalidFirstChar
| UnescapedTilde
deriving (Eq, Show)
unescape :: Text -> Either FormatError Pointer
unescape txt =
case T.splitOn "/" txt of
[] -> Right (Pointer [])
"":xs -> Pointer <$> traverse f xs
_ -> Left InvalidFirstChar
where
f :: Text -> Either FormatError Token
f t = case unescapeToken t of
Nothing -> Left UnescapedTilde
Just tok -> Right tok
newtype Key
= Key { _unKey :: Text }
deriving (Eq, Show, Generic)
instance HA.Hashable Key
newtype Index
= Index { _unIndex :: Int }
deriving (Eq, Show, Generic)
instance HA.Hashable Index
unescapeToken :: Text -> Maybe Token
unescapeToken t
| not (isValid t) = Nothing
| otherwise = Just . Token . replace $ t
where
isValid :: Text -> Bool
isValid x = all (\y -> T.isPrefixOf "0" y || T.isPrefixOf "1" y) afterTildes
where
afterTildes :: [Text]
afterTildes = drop 1 $ T.splitOn "~" x
replace :: Text -> Text
replace = T.replace "~0" "~" . T.replace "~1" "/"
resolveToken :: Token -> Value -> Either ResolutionError Value
resolveToken tok (Array vs) =
case readMaybe . T.unpack . _unToken $ tok of
Nothing -> Left ArrayIndexInvalid
Just n -> do
when (n < 0) (Left ArrayIndexInvalid)
case vs V.!? n of
Nothing -> Left ArrayElemNotFound
Just res -> Right res
resolveToken tok (Object h) =
case HM.lookup (_unToken tok) h of
Nothing -> Left ObjectLookupFailed
Just res -> Right res
resolveToken _ _ = Left ExpectedObjectOrArray