{-# LANGUAGE OverloadedStrings #-} module Festung.Frontend.ConvertersSpec (spec) where import Test.Hspec import Festung.Frontend.Converters import qualified Festung.Vault.Persistence as P import Data.Aeson.Types import Data.Aeson import Data.Either import qualified Data.ByteString.Lazy as BS import Data.Text.Encoding (encodeUtf8) import qualified Data.Text as T import Data.ByteString.Builder (toLazyByteString) convert :: (Value -> Parser a) -> BS.ByteString -> Either String a convert p content = parseEither p =<< eitherDecode content serialize :: (a -> Value) -> a -> BS.ByteString serialize e = encode . e integerToByteString :: Integer -> BS.ByteString integerToByteString = BS.fromStrict . encodeUtf8 . T.pack . show unlines' :: [BS.ByteString] -> BS.ByteString unlines' = BS.intercalate "\n" pendingCustomDecimal :: IO () pendingCustomDecimal = pendingWith "This doesn't work without a custom Value which handles decimal/non-decimal" spec :: Spec spec = do describe "vaultObjectParser" $ do let convert' = convert vaultObjectParser it "Parses integer" $ do convert' "1234" `shouldBe` Right (P.IntValue 1234) convert' "0" `shouldBe` Right (P.IntValue 0) it "Validates integers over 64bits" $ do pendingWith "Not important right now. But needs to be implemented some day™" let bigInteger = (2 ^ 64 + 1) :: Integer convert' (integerToByteString bigInteger) `shouldSatisfy` isLeft it "Parses floats" $ do convert' "3.14" `shouldBe` Right (P.FloatValue 3.14) convert' "1E-1" `shouldBe` Right (P.FloatValue 0.1) it "Parses float without decimals" $ do pendingCustomDecimal convert' "1.0" `shouldBe` Right (P.FloatValue 1.0) convert' "2.0e5" `shouldBe` Right (P.FloatValue 200000) it "Parses strings" $ convert' "\"Hello\"" `shouldBe` Right (P.StringValue "Hello") it "Parses unicode (in this case the snowman character)" $ convert' "\"\\u2603\"" `shouldBe` Right (P.StringValue "☃") it "Parses NULL values" $ convert' "null" `shouldBe` Right P.NullValue it "Prevents bad data" $ do convert' "{}" `shouldSatisfy` isLeft convert' "[]" `shouldSatisfy` isLeft convert' "{\"foo\": \"bar\"}" `shouldSatisfy` isLeft convert' "[1, 2, 3.5]" `shouldSatisfy` isLeft it "Parses blobs" $ do pending let expected = P.BlobValue [0xDE, 0xAD, 0xBE, 0xEF] content = "{\"type\": \"blob\", \"value\": [0xDE, 0xAD, 0xBE, 0xEF]}" convert' content `shouldBe` Right expected it "Validates blob data" $ do pending convert' "{\"type\": \"blob\", \"value\": [0xFFFF, 0xFF]}" `shouldSatisfy` isLeft describe "parametersParser" $ do let convert' = convert parametersParser it "Parses hereterogeneous lists" $ convert' "[1234, \"Hello\", null]" `shouldBe` Right [ P.IntValue 1234 , P.StringValue "Hello" , P.NullValue ] it "Preserves order" $ do convert' "[7, 8]" `shouldBe` Right [ P.IntValue 7, P.IntValue 8 ] convert' "[8, 7]" `shouldBe` Right [ P.IntValue 8, P.IntValue 7 ] it "Parses empty list" $ convert' "[]" `shouldBe` Right [] describe "queryParser" $ do let convert' = convert queryParser it "Parses query object" $ do let content = unlines' [ "{" , " \"sql\": \"SELECT * FROM table WHERE a = ? AND b = ?\"," , " \"params\": [1, \"string\"]" , "}" ] params = [P.IntValue 1, P.StringValue "string"] sql = "SELECT * FROM table WHERE a = ? AND b = ?" convert' content `shouldBe` Right (sql, params) it "Defaults the parameters to empty string" $ do let content = unlines' [ "{" , " \"sql\": \"SELECT * FROM table\"" , "}" ] convert' content `shouldBe` Right ("SELECT * FROM table", []) describe "vaultObjectEncoder" $ do let serialize' = serialize vaultObjectEncoder it "Encodes integer" $ serialize' (P.IntValue 1) `shouldBe` "1" it "Encodes floats" $ serialize' (P.FloatValue 3.14) `shouldBe` "3.14" it "Encodes string" $ serialize' (P.StringValue "Hello World") `shouldBe` "\"Hello World\"" it "Preserves the float type for floats without decimals" $ do pendingCustomDecimal serialize' (P.FloatValue 1.0) `shouldNotBe` "1" it "Encodes null" $ serialize' P.NullValue `shouldBe` "null" describe "rowEncoder" $ do let serialize' = serialize rowEncoder it "Preserves order" $ do serialize' [P.IntValue 1, P.NullValue] `shouldBe` "[1,null]" serialize' [P.NullValue, P.IntValue 1] `shouldBe` "[null,1]"