{-# LANGUAGE OverloadedStrings #-} module Kubernetes.Data.K8sJSONPath where import Data.Aeson import Data.Aeson.Text import Data.JSONPath import Data.Monoid ((<>)) import Data.Text as Text import Control.Applicative ((<|>)) import Data.Attoparsec.Text import Data.Text.Lazy (toStrict) data K8sPathElement = PlainText Text | JSONPath [JSONPathElement] deriving (Int -> K8sPathElement -> ShowS [K8sPathElement] -> ShowS K8sPathElement -> String (Int -> K8sPathElement -> ShowS) -> (K8sPathElement -> String) -> ([K8sPathElement] -> ShowS) -> Show K8sPathElement forall a. (Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a showList :: [K8sPathElement] -> ShowS $cshowList :: [K8sPathElement] -> ShowS show :: K8sPathElement -> String $cshow :: K8sPathElement -> String showsPrec :: Int -> K8sPathElement -> ShowS $cshowsPrec :: Int -> K8sPathElement -> ShowS Show, K8sPathElement -> K8sPathElement -> Bool (K8sPathElement -> K8sPathElement -> Bool) -> (K8sPathElement -> K8sPathElement -> Bool) -> Eq K8sPathElement forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a /= :: K8sPathElement -> K8sPathElement -> Bool $c/= :: K8sPathElement -> K8sPathElement -> Bool == :: K8sPathElement -> K8sPathElement -> Bool $c== :: K8sPathElement -> K8sPathElement -> Bool Eq) k8sJSONPath :: Parser [K8sPathElement] k8sJSONPath :: Parser [K8sPathElement] k8sJSONPath = Parser Text K8sPathElement -> Parser [K8sPathElement] forall (f :: * -> *) a. Alternative f => f a -> f [a] many1 Parser Text K8sPathElement pathElementParser pathElementParser :: Parser K8sPathElement pathElementParser :: Parser Text K8sPathElement pathElementParser = Parser Text K8sPathElement jsonpathParser Parser Text K8sPathElement -> Parser Text K8sPathElement -> Parser Text K8sPathElement forall (f :: * -> *) a. Alternative f => f a -> f a -> f a <|> Parser Text K8sPathElement plainTextParser plainTextParser :: Parser K8sPathElement plainTextParser :: Parser Text K8sPathElement plainTextParser = Text -> K8sPathElement PlainText (Text -> K8sPathElement) -> Parser Text Text -> Parser Text K8sPathElement forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (Char -> Bool) -> Parser Text Text takeWhile1 (Char -> Char -> Bool forall a. Eq a => a -> a -> Bool /= Char '{') jsonpathParser :: Parser K8sPathElement jsonpathParser :: Parser Text K8sPathElement jsonpathParser = [JSONPathElement] -> K8sPathElement JSONPath ([JSONPathElement] -> K8sPathElement) -> Parser Text [JSONPathElement] -> Parser Text K8sPathElement forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b <$> (Char -> Parser Char char Char '{' Parser Char -> Parser Text [JSONPathElement] -> Parser Text [JSONPathElement] forall (f :: * -> *) a b. Applicative f => f a -> f b -> f b *> Parser Text [JSONPathElement] jsonPath Parser Text [JSONPathElement] -> Parser Char -> Parser Text [JSONPathElement] forall (f :: * -> *) a b. Applicative f => f a -> f b -> f a <* Char -> Parser Char char Char '}') runJSONPath :: [K8sPathElement] -> Value -> Either String Text runJSONPath :: [K8sPathElement] -> Value -> Either String Text runJSONPath [] Value _ = Text -> Either String Text forall (f :: * -> *) a. Applicative f => a -> f a pure Text "" runJSONPath (K8sPathElement e:[K8sPathElement] es) Value v = do Text res <- K8sPathElement -> Value -> Either String Text runPathElement K8sPathElement e Value v Text rest <- [K8sPathElement] -> Value -> Either String Text runJSONPath [K8sPathElement] es Value v Text -> Either String Text forall (f :: * -> *) a. Applicative f => a -> f a pure (Text -> Either String Text) -> Text -> Either String Text forall a b. (a -> b) -> a -> b $ Text res Text -> Text -> Text forall a. Semigroup a => a -> a -> a <> Text rest runPathElement :: K8sPathElement -> Value -> Either String Text runPathElement :: K8sPathElement -> Value -> Either String Text runPathElement (PlainText Text t) Value _ = Text -> Either String Text forall (f :: * -> *) a. Applicative f => a -> f a pure Text t runPathElement (JSONPath [JSONPathElement] p) Value v = ExecutionResult Value -> Either String Text encodeResult (ExecutionResult Value -> Either String Text) -> ExecutionResult Value -> Either String Text forall a b. (a -> b) -> a -> b $ [JSONPathElement] -> Value -> ExecutionResult Value executeJSONPath [JSONPathElement] p Value v encodeResult :: ExecutionResult Value -> Either String Text encodeResult :: ExecutionResult Value -> Either String Text encodeResult (ResultValue Value val) = Text -> Either String Text forall (m :: * -> *) a. Monad m => a -> m a return (Text -> Either String Text) -> Text -> Either String Text forall a b. (a -> b) -> a -> b $ Value -> Text jsonToText Value val encodeResult (ResultList [Value] vals) = Text -> Either String Text forall (m :: * -> *) a. Monad m => a -> m a return (Text -> Either String Text) -> Text -> Either String Text forall a b. (a -> b) -> a -> b $ (Text -> [Text] -> Text intercalate Text " " ([Text] -> Text) -> [Text] -> Text forall a b. (a -> b) -> a -> b $ (Value -> Text) -> [Value] -> [Text] forall a b. (a -> b) -> [a] -> [b] Prelude.map Value -> Text jsonToText [Value] vals) encodeResult (ResultError String err) = String -> Either String Text forall a b. a -> Either a b Left String err jsonToText :: Value -> Text jsonToText :: Value -> Text jsonToText (String Text t) = Text t jsonToText Value x = Text -> Text toStrict (Text -> Text) -> Text -> Text forall a b. (a -> b) -> a -> b $ Value -> Text forall a. ToJSON a => a -> Text encodeToLazyText Value x