okapi/test/Spec.hs

110 lines
3.8 KiB
Haskell
Raw Normal View History

{-# LANGUAGE ApplicativeDo #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
{-# LANGUAGE OverloadedRecordDot #-}
2022-07-03 09:46:12 +03:00
{-# LANGUAGE OverloadedStrings #-}
2023-04-15 23:39:54 +03:00
{-# LANGUAGE RecordWildCards #-}
{-# LANGUAGE TypeApplications #-}
import Control.Exception (evaluate)
import qualified Data.Text as Text
import qualified Okapi.Endpoint.Path as Path
2023-04-15 23:39:54 +03:00
import qualified Okapi.Endpoint.Query as Query
import Test.Hspec
import qualified Web.HttpApiData as Web
2022-08-04 03:22:25 +03:00
2022-03-30 03:07:37 +03:00
main :: IO ()
main = hspec $ do
2023-04-15 23:39:54 +03:00
describe "Path Operations" $ do
it "returns the first element of a list" $ do
Path.eval path1 ["index"] `shouldBe` (Right (), [])
it "returns the first element of a list" $ do
Path.eval path1 ["index", "about"] `shouldBe` (Left Path.NotEnoughOperations, ["index", "about"])
it "returns the first element of a list" $ do
Path.eval path2 ["item", "5"] `shouldBe` (Right 5, [])
it "returns the first element of a list" $ do
Path.eval path2 ["item"] `shouldBe` (Left Path.TooManyOperations, ["item"])
it "returns the first element of a list" $ do
Path.eval path3 ["product", "books", "56708"] `shouldBe` (Right (Category "books", ProductID 56708), [])
it "returns the first element of a list" $ do
Path.eval path3 ["product", "books", "56708", "info"] `shouldBe` (Left Path.NotEnoughOperations, ["product", "books", "56708", "info"])
it "returns the first element of a list" $ do
Path.eval path3 ["product", "books"] `shouldBe` (Left Path.TooManyOperations, ["product", "books"])
it "returns the first element of a list" $ do
Path.eval path3' ["product", "books", "56708"] `shouldBe` (Right (Category "books", ProductID 56708), [])
it "returns the first element of a list" $ do
Path.eval path3' ["product", "books", "56708", "info"] `shouldBe` (Left Path.NotEnoughOperations, ["product", "books", "56708", "info"])
it "returns the first element of a list" $ do
Path.eval path3' ["product", "books"] `shouldBe` (Left Path.TooManyOperations, ["product", "books"])
2023-04-15 23:39:54 +03:00
describe "Query Operations" $ do
it "returns the first element of a list" $ do
Query.eval query1 [("score", Just "5"), ("user", Just "Joe")] `shouldBe` (Right $ Filter 5 $ Username "Joe", [])
2023-04-15 23:39:54 +03:00
it "returns the first element of a list" $ do
Query.eval query2 [("user", Just "Bob"), ("active", Nothing)] `shouldBe` (Right $ Username "Bob", [])
2023-04-15 23:39:54 +03:00
it "returns the first element of a list" $ do
Query.eval query3 [("username", Just "Bob")] `shouldBe` (Right (Username "Anon", Nothing), [("username", Just "Bob")])
2023-04-15 23:39:54 +03:00
newtype Username = Username {unwrap :: Text.Text}
deriving (Eq, Show, Web.FromHttpApiData)
data Filter = Filter
{ score :: Int,
byUser :: Username
}
deriving (Eq, Show)
query1 :: Query.Query Filter
query1 = do
score <- Query.param @Int "score"
byUser <- Query.param @Username "user"
pure Filter {..}
query2 :: Query.Query Username
query2 = do
username <- Query.param @Username "user"
Query.flag "active"
pure username
query3 :: Query.Query (Username, Maybe ())
query3 = do
user <- Query.option (Username "Anon") $ Query.param "user"
active <- Query.optional $ Query.flag "active"
pure (user, active)
path1 :: Path.Path ()
path1 = Path.static "index"
path2 :: Path.Path Int
path2 = do
Path.static "item"
uuid <- Path.param @Int
pure uuid
newtype Category = Category {unwrap :: Text.Text}
deriving (Eq, Show, Web.FromHttpApiData)
newtype ProductID = ProductID {unwrap :: Int}
deriving (Eq, Show, Web.FromHttpApiData)
path3 :: Path.Path (Category, ProductID)
path3 = Path.static "product" *> ((,) <$> Path.param @Category <*> Path.param @ProductID)
path3' :: Path.Path (Category, ProductID)
path3' = do
Path.static "product"
category <- Path.param @Category
productID <- Path.param @ProductID
pure (category, productID)