purescript-axon/test/Test/Axon.Request.Parts.purs

235 lines
9.0 KiB
Haskell
Raw Normal View History

2024-12-01 23:11:10 +00:00
module Test.Axon.Request.Parts where
import Prelude
2024-12-02 21:54:35 +00:00
import Axon.Header.Typed (ContentType(..))
2024-12-01 23:11:10 +00:00
import Axon.Request (Request)
import Axon.Request as Request
import Axon.Request.Method (Method(..))
2024-12-02 21:54:35 +00:00
import Axon.Request.Parts.Class (Header(..), Json(..), Patch(..), Path(..), Post(..), extractRequestParts)
2024-12-01 23:12:15 +00:00
import Axon.Request.Parts.Path (type (/), IgnoreRest)
2024-12-01 23:11:10 +00:00
import Control.Monad.Error.Class (liftEither, liftMaybe)
import Data.Bifunctor (lmap)
import Data.Either (Either(..))
import Data.Map as Map
import Data.Maybe (Maybe(..), fromJust)
import Data.Tuple.Nested (type (/\), (/\))
import Data.URL as URL
import Effect.Class (liftEffect)
import Effect.Exception (error)
import Effect.Unsafe (unsafePerformEffect)
import Node.Buffer as Buffer
import Node.Encoding (Encoding(..))
import Node.Net.SocketAddress as SocketAddress
import Node.Stream as Stream
import Partial.Unsafe (unsafePartial)
import Test.Spec (Spec, describe, it)
import Test.Spec.Assertions (shouldEqual)
2024-12-02 21:54:35 +00:00
import Type.MIME as MIME
2024-12-01 23:11:10 +00:00
spec :: Spec Unit
spec = describe "Parts" do
it "extracts the whole request" do
2024-12-01 23:14:19 +00:00
req <- liftEffect $ Request.make
{ body: Request.BodyEmpty
, url: URL.fromString "http://localhost:80/foo" # unsafePartial fromJust
2024-12-02 21:54:35 +00:00
, headers: Map.singleton "content-type" "application/json"
2024-12-01 23:14:19 +00:00
, address: Left $ unsafePerformEffect $ SocketAddress.newIpv4
{ address: "127.0.0.1", port: 81 }
, method: GET
}
void $ extractRequestParts @Request req <#> lmap (error <<< show)
>>= liftEither
>>= liftMaybe (error "was nothing")
2024-12-01 23:11:10 +00:00
2024-12-02 21:54:35 +00:00
it "extracts header, method, path, JSON body" do
2024-12-01 23:14:19 +00:00
stream <- Buffer.fromString """{"firstName": "henry"}""" UTF8
>>= Stream.readableFromBuffer
# liftEffect
req <- liftEffect $ Request.make
{ body: Request.BodyReadable stream
, url: URL.fromString "http://localhost:80/users/12" # unsafePartial
fromJust
2024-12-02 21:54:35 +00:00
, headers: Map.singleton "content-type" "application/json"
2024-12-01 23:14:19 +00:00
, address: Left $ unsafePerformEffect $ SocketAddress.newIpv4
{ address: "127.0.0.1", port: 81 }
, method: PATCH
}
a <-
extractRequestParts
2024-12-02 21:54:35 +00:00
@(Patch /\ Header (ContentType MIME.Json) /\ (Path ("users" / Int) _) /\ Json { firstName :: String })
2024-12-01 23:14:19 +00:00
req <#> lmap (error <<< show) >>= liftEither >>= liftMaybe
(error "was nothing")
2024-12-02 21:54:35 +00:00
a `shouldEqual` (Patch /\ Header (ContentType MIME.Json) /\ Path 12 /\ Json { firstName: "henry" })
2024-12-01 23:11:10 +00:00
describe "Path" do
it "matches a route matching literal" do
2024-12-01 23:14:19 +00:00
req <- liftEffect $ Request.make
{ body: Request.BodyCachedString "foo"
, url: URL.fromString "http://localhost:80/foo" # unsafePartial fromJust
, headers: Map.empty
, address: Left $ unsafePerformEffect $ SocketAddress.newIpv4
{ address: "127.0.0.1", port: 81 }
, method: GET
}
a <- extractRequestParts @(Path "foo" _) req <#> lmap (error <<< show)
>>= liftEither
>>= liftMaybe (error "was nothing")
2024-12-01 23:11:10 +00:00
a `shouldEqual` (Path unit)
it "matches a route matching multiple literals" do
2024-12-01 23:14:19 +00:00
req <- liftEffect $ Request.make
{ body: Request.BodyCachedString "foo"
, url: URL.fromString "http://localhost:80/foo/bar/baz" # unsafePartial
fromJust
, headers: Map.empty
, address: Left $ unsafePerformEffect $ SocketAddress.newIpv4
{ address: "127.0.0.1", port: 81 }
, method: GET
}
a <- extractRequestParts @(Path ("foo" / "bar" / "baz") _) req
<#> lmap (error <<< show)
>>= liftEither
>>= liftMaybe (error "was nothing")
2024-12-01 23:11:10 +00:00
a `shouldEqual` (Path unit)
it "does not partially match a route ..." do
req <- liftEffect $ Request.make
{ body: Request.BodyCachedString "foo"
2024-12-01 23:14:19 +00:00
, url: URL.fromString "http://localhost:80/foo/bar/baz" # unsafePartial
fromJust
2024-12-01 23:11:10 +00:00
, headers: Map.empty
2024-12-01 23:14:19 +00:00
, address: Left $ unsafePerformEffect $ SocketAddress.newIpv4
{ address: "127.0.0.1", port: 81 }
2024-12-01 23:11:10 +00:00
, method: GET
}
2024-12-01 23:14:19 +00:00
a <- extractRequestParts @(Path ("foo" / "bar") _) req
<#> lmap (error <<< show)
>>= liftEither
2024-12-01 23:11:10 +00:00
a `shouldEqual` Nothing
it "... but does if ends in IgnoreRest" do
req <- liftEffect $ Request.make
{ body: Request.BodyCachedString "foo"
2024-12-01 23:14:19 +00:00
, url: URL.fromString "http://localhost:80/foo/bar/baz" # unsafePartial
fromJust
2024-12-01 23:11:10 +00:00
, headers: Map.empty
2024-12-01 23:14:19 +00:00
, address: Left $ unsafePerformEffect $ SocketAddress.newIpv4
{ address: "127.0.0.1", port: 81 }
2024-12-01 23:11:10 +00:00
, method: GET
}
2024-12-01 23:14:19 +00:00
a <- extractRequestParts @(Path ("foo" / "bar" / IgnoreRest) _) req
<#> lmap (error <<< show)
>>= liftEither
>>= liftMaybe (error "was nothing")
2024-12-01 23:11:10 +00:00
a `shouldEqual` (Path unit)
it "extracts an int" do
req <- liftEffect $ Request.make
{ body: Request.BodyCachedString "foo"
2024-12-01 23:14:19 +00:00
, url: URL.fromString "http://localhost:80/foo/123/bar" # unsafePartial
fromJust
2024-12-01 23:11:10 +00:00
, headers: Map.empty
2024-12-01 23:14:19 +00:00
, address: Left $ unsafePerformEffect $ SocketAddress.newIpv4
{ address: "127.0.0.1", port: 81 }
2024-12-01 23:11:10 +00:00
, method: GET
}
2024-12-01 23:14:19 +00:00
a <- extractRequestParts @(Path ("foo" / Int / "bar") _) req
<#> lmap (error <<< show)
>>= liftEither
>>= liftMaybe (error "was nothing")
2024-12-01 23:11:10 +00:00
a `shouldEqual` (Path 123)
it "extracts an int and a string" do
req <- liftEffect $ Request.make
{ body: Request.BodyCachedString "foo"
2024-12-01 23:14:19 +00:00
, url: URL.fromString "http://localhost:80/foo/123/bar/baz" #
unsafePartial fromJust
2024-12-01 23:11:10 +00:00
, headers: Map.empty
2024-12-01 23:14:19 +00:00
, address: Left $ unsafePerformEffect $ SocketAddress.newIpv4
{ address: "127.0.0.1", port: 81 }
2024-12-01 23:11:10 +00:00
, method: GET
}
2024-12-01 23:14:19 +00:00
a <- extractRequestParts @(Path ("foo" / Int / "bar" / String) _) req
<#> lmap (error <<< show)
>>= liftEither
>>= liftMaybe (error "was nothing")
2024-12-01 23:11:10 +00:00
a `shouldEqual` (Path $ 123 /\ "baz")
describe "Body" do
it "extracts a string body from a cached string" do
2024-12-01 23:14:19 +00:00
req <- liftEffect $ Request.make
{ body: Request.BodyCachedString "foo"
, url: URL.fromString "http://localhost:80/foo" # unsafePartial fromJust
, headers: Map.empty
, address: Left $ unsafePerformEffect $ SocketAddress.newIpv4
{ address: "127.0.0.1", port: 81 }
, method: GET
}
a <- extractRequestParts @(Either Request.BodyStringError String) req
<#> lmap (error <<< show)
>>= liftEither
>>= liftMaybe (error "was nothing")
2024-12-01 23:11:10 +00:00
a `shouldEqual` (Right "foo")
2024-12-01 23:14:19 +00:00
2024-12-01 23:11:10 +00:00
it "extracts a string body from a readable stream" do
2024-12-01 23:14:19 +00:00
stream <- Buffer.fromString "foo" UTF8 >>= Stream.readableFromBuffer #
liftEffect
req <- liftEffect $ Request.make
{ body: Request.BodyReadable stream
, url: URL.fromString "http://localhost:80/foo" # unsafePartial fromJust
, headers: Map.empty
, address: Left $ unsafePerformEffect $ SocketAddress.newIpv4
{ address: "127.0.0.1", port: 81 }
, method: GET
}
a <- extractRequestParts @(Either Request.BodyStringError String) req
<#> lmap (error <<< show)
>>= liftEither
>>= liftMaybe (error "was nothing")
2024-12-01 23:11:10 +00:00
a `shouldEqual` (Right "foo")
2024-12-01 23:14:19 +00:00
a' <- extractRequestParts @String req <#> lmap (error <<< show)
>>= liftEither
>>= liftMaybe (error "was nothing")
2024-12-01 23:11:10 +00:00
a' `shouldEqual` "foo"
2024-12-01 23:14:19 +00:00
2024-12-01 23:11:10 +00:00
it "extracts a string body from a buffer" do
buf <- Buffer.fromString "foo" UTF8 # liftEffect
2024-12-01 23:14:19 +00:00
req <- liftEffect $ Request.make
{ body: Request.BodyCached buf
, url: URL.fromString "http://localhost:80/foo" # unsafePartial fromJust
, headers: Map.empty
, address: Left $ unsafePerformEffect $ SocketAddress.newIpv4
{ address: "127.0.0.1", port: 81 }
, method: GET
}
a <- extractRequestParts @(Either Request.BodyStringError String) req
<#> lmap (error <<< show)
>>= liftEither
>>= liftMaybe (error "was nothing")
2024-12-01 23:11:10 +00:00
a `shouldEqual` (Right "foo")
2024-12-01 23:14:19 +00:00
a' <- extractRequestParts @String req <#> lmap (error <<< show)
>>= liftEither
>>= liftMaybe (error "was nothing")
2024-12-01 23:11:10 +00:00
a' `shouldEqual` "foo"
2024-12-01 23:14:19 +00:00
2024-12-01 23:11:10 +00:00
it "extracts a JSON body" do
2024-12-01 23:14:19 +00:00
stream <- Buffer.fromString """{"foo": 123, "bar": "abc"}""" UTF8
>>= Stream.readableFromBuffer
# liftEffect
req <- liftEffect $ Request.make
{ body: Request.BodyReadable stream
, url: URL.fromString "http://localhost:80/foo" # unsafePartial fromJust
, headers: Map.empty
, address: Left $ unsafePerformEffect $ SocketAddress.newIpv4
{ address: "127.0.0.1", port: 81 }
, method: POST
}
2024-12-01 23:21:41 +00:00
a <- extractRequestParts @(Post /\ Json { foo :: Int, bar :: String }) req
2024-12-01 23:14:19 +00:00
<#> lmap (error <<< show)
>>= liftEither
>>= liftMaybe (error "was nothing")
2024-12-01 23:21:41 +00:00
a `shouldEqual` (Post /\ Json { foo: 123, bar: "abc" })