diff --git a/.gitignore b/.gitignore index e2a29a9..2dc5c4b 100644 --- a/.gitignore +++ b/.gitignore @@ -3,3 +3,4 @@ /.psc* /.purs* /.psa* +/.dir-locals.el diff --git a/Documentation/Examples/HelloWorld/Main.purs b/Documentation/Examples/HelloWorld/Main.purs index 13a2c0e..5134933 100644 --- a/Documentation/Examples/HelloWorld/Main.purs +++ b/Documentation/Examples/HelloWorld/Main.purs @@ -1,8 +1,9 @@ module HelloWorld where -import Prelude (discard, show, (<>), ($)) +import Prelude (discard, pure, show, (<>), ($)) import Control.Monad.Eff.Console as Console +import Data.StrMap as StrMap import HTTPure as HTTPure -- | Serve the example server on this port @@ -13,19 +14,13 @@ port = 8080 portS :: String portS = show port --- | Specify the routes -routes :: forall e. Array (HTTPure.Route e) -routes = - [ HTTPure.Get "/" - { status: \_ -> 200 - , headers: \_ -> [] - , body: \_ -> "hello world!" - } - ] +-- | Say 'hello world!' when run +sayHello :: forall e. HTTPure.Request -> HTTPure.ResponseM e +sayHello _ = pure $ HTTPure.OK StrMap.empty "hello world!" -- | Boot up the server -main :: forall e. HTTPure.HTTPureM (console :: Console.CONSOLE | e) -main = HTTPure.serve port routes do +main :: forall e. HTTPure.ServerM (console :: Console.CONSOLE | e) +main = HTTPure.serve port sayHello do Console.log $ "" Console.log $ " ┌────────────────────────────────────────────┐" Console.log $ " │ Server now up on port " <> portS <> " │" diff --git a/Documentation/Examples/HelloWorld/Readme.md b/Documentation/Examples/HelloWorld/Readme.md index de1c1f7..e6a9da4 100644 --- a/Documentation/Examples/HelloWorld/Readme.md +++ b/Documentation/Examples/HelloWorld/Readme.md @@ -1,7 +1,7 @@ # Hello World Example This is a basic 'hello world' example. It simply returns 'hello world!' when -requesting '/' via an HTTP GET. +making any request. To run the example server, run: diff --git a/Documentation/Examples/MultiRoute/Main.purs b/Documentation/Examples/MultiRoute/Main.purs index 5053d4b..50a30aa 100644 --- a/Documentation/Examples/MultiRoute/Main.purs +++ b/Documentation/Examples/MultiRoute/Main.purs @@ -1,8 +1,9 @@ module MultiRoute where -import Prelude (discard, show, (<>), ($)) +import Prelude (discard, pure, show, (<>), ($)) import Control.Monad.Eff.Console as Console +import Data.StrMap as StrMap import HTTPure as HTTPure -- | Serve the example server on this port @@ -14,23 +15,14 @@ portS :: String portS = show port -- | Specify the routes -routes :: forall e. Array (HTTPure.Route e) -routes = - [ HTTPure.Get "/hello" - { status: \_ -> 200 - , headers: \_ -> [] - , body: \_ -> "hello" - } - , HTTPure.Get "/goodbye" - { status: \_ -> 200 - , headers: \_ -> [] - , body: \_ -> "goodbye" - } - ] +router :: forall e. HTTPure.Request -> HTTPure.ResponseM e +router (HTTPure.Get _ "/hello") = pure $ HTTPure.OK StrMap.empty "hello" +router (HTTPure.Get _ "/goodbye") = pure $ HTTPure.OK StrMap.empty "goodbye" +router _ = pure $ HTTPure.OK StrMap.empty "" -- | Boot up the server -main :: forall e. HTTPure.HTTPureM (console :: Console.CONSOLE | e) -main = HTTPure.serve port routes do +main :: forall e. HTTPure.ServerM (console :: Console.CONSOLE | e) +main = HTTPure.serve port router do Console.log $ "" Console.log $ " ┌───────────────────────────────────────────────┐" Console.log $ " │ Server now up on port " <> portS <> " │" diff --git a/Library/HTTPure.purs b/Library/HTTPure.purs index e53b3f7..692928e 100644 --- a/Library/HTTPure.purs +++ b/Library/HTTPure.purs @@ -1,11 +1,9 @@ module HTTPure - ( module HTTPure.HTTPureM - , module HTTPure.Request - , module HTTPure.Route + ( module HTTPure.Request + , module HTTPure.Response , module HTTPure.Server ) where -import HTTPure.HTTPureM (HTTPureEffects, HTTPureM) -import HTTPure.Request (Request, getURL) -import HTTPure.Route (Route(..)) -import HTTPure.Server (serve) +import HTTPure.Request (Request(..)) +import HTTPure.Response (ResponseM, Response(..)) +import HTTPure.Server (ServerM, serve) diff --git a/Library/HTTPure/Body.purs b/Library/HTTPure/Body.purs new file mode 100644 index 0000000..05a769d --- /dev/null +++ b/Library/HTTPure/Body.purs @@ -0,0 +1,7 @@ +module HTTPure.Body + ( Body + ) where + +-- | The Body type is just sugar for a String, that will be sent or received in +-- | the HTTP body. +type Body = String diff --git a/Library/HTTPure/HTTPureM.purs b/Library/HTTPure/HTTPureM.purs index ed6e409..9b785aa 100644 --- a/Library/HTTPure/HTTPureM.purs +++ b/Library/HTTPure/HTTPureM.purs @@ -1,6 +1,5 @@ module HTTPure.HTTPureM - ( HTTPureEffects - , HTTPureM + ( HTTPureM ) where import Prelude (Unit) @@ -8,13 +7,7 @@ import Prelude (Unit) import Control.Monad.Eff as Eff import Node.HTTP as HTTP --- | The `HTTPureMEffects` type is a row that wraps up all HTTPure effects. --- | Under the hood this uses Node.HTTP, but it could be replaced by another --- | adapter. -type HTTPureEffects e = (http :: HTTP.HTTP | e) - --- | The `HTTPureM` monad represents actions acting over an HTTPure server --- | lifecycle. It is the return type of all route handlers and of the `serve` --- | function. It takes an effects row parameter which enumerates all other --- | side-effects performed while carrying out the server actions. -type HTTPureM e = Eff.Eff (HTTPureEffects e) Unit +-- | The `HTTPureM` monad represents effects run by an HTTPure server. It takes +-- | an effects row parameter which enumerates all other side-effects performed +-- | while carrying out the server actions. +type HTTPureM e t = Eff.Eff (http :: HTTP.HTTP | e) t diff --git a/Library/HTTPure/Headers.purs b/Library/HTTPure/Headers.purs new file mode 100644 index 0000000..cb52260 --- /dev/null +++ b/Library/HTTPure/Headers.purs @@ -0,0 +1,9 @@ +module HTTPure.Headers + ( Headers + ) where + +import Data.StrMap as StrMap + +-- | The Headers type is just sugar for a StrMap of Strings that represents the +-- | set of headers sent or received in an HTTP request or response. +type Headers = StrMap.StrMap String diff --git a/Library/HTTPure/Path.purs b/Library/HTTPure/Path.purs new file mode 100644 index 0000000..948f61b --- /dev/null +++ b/Library/HTTPure/Path.purs @@ -0,0 +1,7 @@ +module HTTPure.Path + ( Path + ) where + +-- | The Path type is just sugar for a String that will be sent in a request and +-- | indicates the path of the resource being requested. +type Path = String diff --git a/Library/HTTPure/Request.purs b/Library/HTTPure/Request.purs index fdd03ba..3d8f0bd 100644 --- a/Library/HTTPure/Request.purs +++ b/Library/HTTPure/Request.purs @@ -1,32 +1,41 @@ module HTTPure.Request - ( Request + ( Request(..) , fromHTTPRequest - , getURL ) where +import Prelude ((<>)) + +import Data.Show as Show import Node.HTTP as HTTP -import Node.Stream as Stream --- | The Request type takes as it's parameter an effects row. It is a Record --- | type with two fields: --- | --- | - `httpRequest`: The raw underlying HTTP request. --- | - `stream`: The raw request converted to a Readable stream. --- | --- | Neither field is intended to be accessed directly, rather it is recommended --- | to use the methods exported by this module. -type Request e = - { httpRequest :: HTTP.Request - , stream :: Stream.Readable () (http :: HTTP.HTTP | e) - } +import HTTPure.Body as Body +import HTTPure.Headers as Headers +import HTTPure.Path as Path --- | Convert a Node.HTTP Request into a HTTPure Request. -fromHTTPRequest :: forall e. HTTP.Request -> Request e +-- | A Request is a method along with headers, a path, and sometimes a body. +data Request + = Get Headers.Headers Path.Path + | Post Headers.Headers Path.Path Body.Body + | Put Headers.Headers Path.Path Body.Body + | Delete Headers.Headers Path.Path + +-- | When using show on a Request, print the method and the path. +instance show :: Show.Show Request where + show (Get _ path) = "GET: " <> path + show (Post _ path _) = "POST: " <> path + show (Put _ path _) = "PUT: " <> path + show (Delete _ path) = "DELETE: " <> path + +-- | Given an HTTP Request object, this method will convert it to an HTTPure +-- | Request object. +fromHTTPRequest :: HTTP.Request -> Request fromHTTPRequest request = - { httpRequest: request - , stream: HTTP.requestAsStream request - } - --- | Get the URL used to generate a Request. -getURL :: forall e. Request e -> String -getURL request = HTTP.requestURL request.httpRequest + case method of + "POST" -> Post headers path "" + "PUT" -> Put headers path "" + "DELETE" -> Delete headers path + _ -> Get headers path + where + method = HTTP.requestMethod request + headers = HTTP.requestHeaders request + path = HTTP.requestURL request diff --git a/Library/HTTPure/Response.purs b/Library/HTTPure/Response.purs index d722977..e6780b3 100644 --- a/Library/HTTPure/Response.purs +++ b/Library/HTTPure/Response.purs @@ -1,41 +1,37 @@ module HTTPure.Response - ( Response - , fromHTTPResponse - , write + ( ResponseM + , Response(..) + , send ) where import Prelude (Unit, bind, discard, pure, unit) -import Control.Monad.Eff as Eff import Node.Encoding as Encoding import Node.HTTP as HTTP import Node.Stream as Stream --- | The Response type takes as it's parameter an effects row. It is a Record --- | type with two fields: --- | --- | - `httpResponse`: The raw underlying HTTP response. --- | - `stream`: The raw response converted to a Writable stream. --- | --- | Neither field is intended to be accessed directly, rather it is recommended --- | to use the methods exported by this module. -type Response e = - { httpResponse :: HTTP.Response - , stream :: Stream.Writable () (http :: HTTP.HTTP | e) - } +import HTTPure.Body as Body +import HTTPure.Headers as Headers +import HTTPure.HTTPureM as HTTPureM --- | Convert a Node.HTTP Response into a HTTPure Response. -fromHTTPResponse :: forall e. HTTP.Response -> Response e -fromHTTPResponse response = - { httpResponse: response - , stream: HTTP.responseAsStream response - } +-- | A response is a status, and can have headers and a body. Different response +-- | codes will allow different response components to be sent. +data Response + = OK Headers.Headers Body.Body --- | Write a string into the Response output. -write :: forall e. Response e -> String -> Eff.Eff (http :: HTTP.HTTP | e) Unit -write response str = do - _ <- Stream.writeString response.stream Encoding.UTF8 str noop - Stream.end response.stream noop +-- | The ResponseM type simply conveniently wraps up an HTTPure monad that +-- | returns a response. This type is the return type of all router/route +-- | methods. +type ResponseM e = HTTPureM.HTTPureM e Response + +-- | Given an HTTP response and a HTTPure response, this method will return a +-- | monad encapsulating writing the HTTPure response to the HTTP response and +-- | closing the HTTP response. +send :: forall e. HTTP.Response -> Response -> HTTPureM.HTTPureM e Unit +send response (OK headers body) = do + _ <- Stream.writeString stream Encoding.UTF8 body noop + Stream.end stream noop noop where + stream = HTTP.responseAsStream response noop = pure unit diff --git a/Library/HTTPure/Route.purs b/Library/HTTPure/Route.purs deleted file mode 100644 index ecdb33e..0000000 --- a/Library/HTTPure/Route.purs +++ /dev/null @@ -1,73 +0,0 @@ -module HTTPure.Route - ( Route(..) - , RouteHooks - , run - , match - , isMatch - ) where - -import Prelude (flip, ($), (==), (>>=), (<>)) - -import Data.Array as Array -import Data.Eq as Eq -import Data.Maybe as Maybe -import Data.Show as Show - -import HTTPure.HTTPureM as HTTPureM -import HTTPure.Request as Request -import HTTPure.Response as Response - -type RouteHooks e = - { status :: Request.Request e -> Int - , body :: Request.Request e -> String - , headers :: Request.Request e -> Array String - } - --- | A Route matches a given HTTP Method against a given path matcher string. --- | When a request comes in that matches the route, the body function is --- | executed against the request and the result is sent back to the client. -data Route e - = Get String (RouteHooks e) - | Post String (RouteHooks e) - | Put String (RouteHooks e) - | Delete String (RouteHooks e) - --- | When calling `show` on a route, display the method and the matching --- | pattern. -instance show :: Show.Show (Route e) where - show (Get pattern _) = "GET: " <> pattern - show (Post pattern _) = "POST: " <> pattern - show (Put pattern _) = "PUT: " <> pattern - show (Delete pattern _) = "DELETE: " <> pattern - --- | Two routes are equal if they are the same method and have the same matching --- | pattern. -instance eq :: Eq.Eq (Route e) where - eq (Get pattern1 _) (Get pattern2 _) = pattern1 == pattern2 - eq (Post pattern1 _) (Post pattern2 _) = pattern1 == pattern2 - eq (Put pattern1 _) (Put pattern2 _) = pattern1 == pattern2 - eq (Delete pattern1 _) (Delete pattern2 _) = pattern1 == pattern2 - eq _ _ = false - --- | Given a route and a request, return the response body. -run :: forall e. - Route e -> - Request.Request e -> - Response.Response e -> - HTTPureM.HTTPureM e -run (Get _ { body: body }) req resp = Response.write resp $ body req -run (Post _ { body: body }) req resp = Response.write resp $ body req -run (Put _ { body: body }) req resp = Response.write resp $ body req -run (Delete _ { body: body }) req resp = Response.write resp $ body req - --- | Returns true if the request matches the route. -isMatch :: forall e. Route e -> Request.Request e -> Boolean -isMatch (Get matcher _) request = matcher == Request.getURL request -isMatch (Post matcher _) request = matcher == Request.getURL request -isMatch (Put matcher _) request = matcher == Request.getURL request -isMatch (Delete matcher _) request = matcher == Request.getURL request - --- | Returns the matching route for the request. -match :: forall e. Array (Route e) -> Request.Request e -> Maybe.Maybe (Route e) -match routes request = - Array.findIndex (flip isMatch request) routes >>= Array.index routes diff --git a/Library/HTTPure/Server.purs b/Library/HTTPure/Server.purs index aec046b..1655404 100644 --- a/Library/HTTPure/Server.purs +++ b/Library/HTTPure/Server.purs @@ -1,10 +1,11 @@ module HTTPure.Server - ( boot, - handleRequest, - serve + ( ServerM + , boot + , handleRequest + , serve ) where -import Prelude (pure, unit, (>>=)) +import Prelude (Unit, (>>=)) import Data.Maybe as Maybe import Node.HTTP as HTTP @@ -12,44 +13,44 @@ import Node.HTTP as HTTP import HTTPure.HTTPureM as HTTPureM import HTTPure.Request as Request import HTTPure.Response as Response -import HTTPure.Route as Route --- | This function takes an array of Routes, a request, and a response, and --- | routes the request to the correct Routes. After the Routes have run, this --- | function closes the request stream. +-- | The ResponseM type simply conveniently wraps up an HTTPure monad that +-- | returns a Unit. This type is the return type of the HTTPure serve and +-- | related methods. +type ServerM e = HTTPureM.HTTPureM e Unit + +-- | This function a method which takes a request and returns a ResponseM, an +-- | HTTP request, and an HTTP response. It runs the request, extracts the +-- | Response from the ResponseM, and sends the Response to the HTTP Response. handleRequest :: forall e. - Array (Route.Route e) -> + (Request.Request -> Response.ResponseM e) -> HTTP.Request -> HTTP.Response -> - HTTPureM.HTTPureM e -handleRequest routes request response = - case Route.match routes req of - Maybe.Just route -> Route.run route req resp - Maybe.Nothing -> pure unit - where - req = Request.fromHTTPRequest request - resp = Response.fromHTTPResponse response + ServerM e +handleRequest router request response = + router (Request.fromHTTPRequest request) >>= Response.send response --- | Given an options object, an Array of Routes, and an HTTPureM containing --- | effects to run on boot, creates and runs a HTTPure server. +-- | Given an options object, an function mapping Request to ResponseM, and an +-- | HTTPureM containing effects to run on boot, creates and runs a HTTPure +-- | server. boot :: forall e. HTTP.ListenOptions -> - Array (Route.Route e) -> - HTTPureM.HTTPureM e -> - HTTPureM.HTTPureM e -boot options routes onStarted = - HTTP.createServer (handleRequest routes) >>= \server -> + (Request.Request -> Response.ResponseM e) -> + ServerM e -> + ServerM e +boot options router onStarted = + HTTP.createServer (handleRequest router) >>= \server -> HTTP.listen server options onStarted -- | Create and start a server. This is the main entry point for HTTPure. Takes --- | a port number on which to listen, an Array of Routes to serve, and an --- | HTTPureM containing effects to run after the server has booted (usually --- | logging). Returns an HTTPureM containing the server's effects. +-- | a port number on which to listen, a function mapping Request to ResponseM, +-- | and an HTTPureM containing effects to run after the server has booted +-- | (usually logging). Returns an HTTPureM containing the server's effects. serve :: forall e. Int -> - Array (Route.Route e) -> - HTTPureM.HTTPureM e -> - HTTPureM.HTTPureM e + (Request.Request -> Response.ResponseM e) -> + ServerM e -> + ServerM e serve port = boot { hostname: "localhost" , port: port diff --git a/Test/HTTPure/BodySpec.purs b/Test/HTTPure/BodySpec.purs new file mode 100644 index 0000000..50414b5 --- /dev/null +++ b/Test/HTTPure/BodySpec.purs @@ -0,0 +1,11 @@ +module HTTPure.BodySpec where + +import Prelude (pure, unit) + +import Test.Spec as Spec + +import HTTPure.SpecHelpers as SpecHelpers + +bodySpec :: SpecHelpers.Test +bodySpec = Spec.describe "Body" do + pure unit diff --git a/Test/HTTPure/HTTPureMSpec.purs b/Test/HTTPure/HTTPureMSpec.purs index c148f27..1a0a3bc 100644 --- a/Test/HTTPure/HTTPureMSpec.purs +++ b/Test/HTTPure/HTTPureMSpec.purs @@ -1,11 +1,11 @@ module HTTPure.HTTPureMSpec where -import Prelude (pure, unit, ($)) +import Prelude (pure, unit) import Test.Spec as Spec import HTTPure.SpecHelpers as SpecHelpers httpureMSpec :: SpecHelpers.Test -httpureMSpec = Spec.describe "HTTPureM" $ +httpureMSpec = Spec.describe "HTTPureM" do pure unit diff --git a/Test/HTTPure/HeadersSpec.purs b/Test/HTTPure/HeadersSpec.purs new file mode 100644 index 0000000..296c8eb --- /dev/null +++ b/Test/HTTPure/HeadersSpec.purs @@ -0,0 +1,11 @@ +module HTTPure.HeadersSpec where + +import Prelude (pure, unit) + +import Test.Spec as Spec + +import HTTPure.SpecHelpers as SpecHelpers + +headersSpec :: SpecHelpers.Test +headersSpec = Spec.describe "Headers" do + pure unit diff --git a/Test/HTTPure/PathSpec.purs b/Test/HTTPure/PathSpec.purs new file mode 100644 index 0000000..de9e0b0 --- /dev/null +++ b/Test/HTTPure/PathSpec.purs @@ -0,0 +1,11 @@ +module HTTPure.PathSpec where + +import Prelude (pure, unit) + +import Test.Spec as Spec + +import HTTPure.SpecHelpers as SpecHelpers + +pathSpec :: SpecHelpers.Test +pathSpec = Spec.describe "Path" do + pure unit diff --git a/Test/HTTPure/RequestSpec.purs b/Test/HTTPure/RequestSpec.purs index 7af9600..eef6ac0 100644 --- a/Test/HTTPure/RequestSpec.purs +++ b/Test/HTTPure/RequestSpec.purs @@ -1,21 +1,82 @@ module HTTPure.RequestSpec where -import Prelude (($)) +import Prelude (discard, pure, show, unit, (<>), ($)) +import Data.StrMap as StrMap import Test.Spec as Spec import Test.Spec.Assertions as Assertions -import HTTPure.SpecHelpers as SpecHelpers - import HTTPure.Request as Request -getURLSpec :: SpecHelpers.Test -getURLSpec = Spec.describe "getURL" $ - Spec.it "is the URL of the request" $ - Request.getURL req `Assertions.shouldEqual` "/test" - where - req = SpecHelpers.mockRequest "/test" +import HTTPure.SpecHelpers as SpecHelpers + +showSpec :: SpecHelpers.Test +showSpec = Spec.describe "show" do + Spec.describe "with a POST" do + Spec.it "is the method and the path" do + show (Request.Post none "test" "") `Assertions.shouldEqual` "POST: test" + Spec.describe "with a PUT" do + Spec.it "is the method and the path" do + show (Request.Put none "test" "") `Assertions.shouldEqual` "PUT: test" + Spec.describe "with a DELETE" do + Spec.it "is the method and the path" do + show (Request.Delete none "test") `Assertions.shouldEqual` "DELETE: test" + Spec.describe "with a GET" do + Spec.it "is the method and the path" do + show (Request.Get none "test") `Assertions.shouldEqual` "GET: test" + where + none = StrMap.empty + +fromHTTPRequestSpec :: SpecHelpers.Test +fromHTTPRequestSpec = Spec.describe "fromHTTPRequest" do + + Spec.describe "with a POST" do + Spec.it "is a Post" do + case Request.fromHTTPRequest (SpecHelpers.mockRequest "POST" "") of + (Request.Post _ _ _) -> pure unit + a -> Assertions.fail $ "expected a Post, got " <> show a + Spec.pending "has the correct headers" + Spec.it "has the correct path" do + case Request.fromHTTPRequest (SpecHelpers.mockRequest "POST" "test") of + (Request.Post _ "test" _) -> pure unit + a -> Assertions.fail $ "expected the path 'test', got " <> show a + Spec.pending "has the correct body" + + Spec.describe "with a PUT" do + Spec.it "is a Put" do + case Request.fromHTTPRequest (SpecHelpers.mockRequest "PUT" "") of + (Request.Put _ _ _) -> pure unit + a -> Assertions.fail $ "expected a Put, got " <> show a + Spec.pending "has the correct headers" + Spec.it "has the correct path" do + case Request.fromHTTPRequest (SpecHelpers.mockRequest "PUT" "test") of + (Request.Put _ "test" _) -> pure unit + a -> Assertions.fail $ "expected the path 'test', got " <> show a + Spec.pending "has the correct body" + + Spec.describe "with a DELETE" do + Spec.it "is a Delete" do + case Request.fromHTTPRequest (SpecHelpers.mockRequest "DELETE" "") of + (Request.Delete _ _) -> pure unit + a -> Assertions.fail $ "expected a Delete, got " <> show a + Spec.pending "has the correct headers" + Spec.it "has the correct path" do + case Request.fromHTTPRequest (SpecHelpers.mockRequest "DELETE" "test") of + (Request.Delete _ "test") -> pure unit + a -> Assertions.fail $ "expected the path 'test', got " <> show a + + Spec.describe "with a GET" do + Spec.it "is a Get" do + case Request.fromHTTPRequest (SpecHelpers.mockRequest "GET" "") of + (Request.Get _ _) -> pure unit + a -> Assertions.fail $ "expected a Get, got " <> show a + Spec.it "has the correct path" do + case Request.fromHTTPRequest (SpecHelpers.mockRequest "GET" "test") of + (Request.Get _ "test") -> pure unit + a -> Assertions.fail $ "expected the path 'test', got " <> show a + Spec.pending "has the correct headers" requestSpec :: SpecHelpers.Test -requestSpec = Spec.describe "Request" $ - getURLSpec +requestSpec = Spec.describe "Request" do + showSpec + fromHTTPRequestSpec diff --git a/Test/HTTPure/ResponseSpec.purs b/Test/HTTPure/ResponseSpec.purs index 5fa8415..2b2ca19 100644 --- a/Test/HTTPure/ResponseSpec.purs +++ b/Test/HTTPure/ResponseSpec.purs @@ -3,24 +3,28 @@ module HTTPure.ResponseSpec where import Prelude (bind, discard, ($)) import Control.Monad.Eff.Class as EffClass +import Data.StrMap as StrMap import Node.Encoding as Encoding import Node.StreamBuffer as StreamBuffer import Test.Spec as Spec import Test.Spec.Assertions as Assertions -import HTTPure.SpecHelpers as SpecHelpers - import HTTPure.Response as Response -writeSpec :: SpecHelpers.Test -writeSpec = Spec.describe "write" $ - Spec.it "sets the response body" do - body <- EffClass.liftEff do - buf <- StreamBuffer.writable - Response.write (SpecHelpers.mockResponse buf) "test" - StreamBuffer.contents Encoding.UTF8 buf - body `Assertions.shouldEqual` "test" +import HTTPure.SpecHelpers as SpecHelpers + +sendSpec :: SpecHelpers.Test +sendSpec = Spec.describe "send" do + Spec.describe "with an OK" do + Spec.pending "writes the headers" + Spec.it "writes the body" do + body <- EffClass.liftEff do + buf <- StreamBuffer.writable + let resp = SpecHelpers.mockResponse buf + Response.send resp $ Response.OK StrMap.empty "test" + StreamBuffer.contents Encoding.UTF8 buf + body `Assertions.shouldEqual` "test" responseSpec :: SpecHelpers.Test -responseSpec = Spec.describe "Response" $ - writeSpec +responseSpec = Spec.describe "Response" do + sendSpec diff --git a/Test/HTTPure/RouteSpec.purs b/Test/HTTPure/RouteSpec.purs deleted file mode 100644 index 3c7638f..0000000 --- a/Test/HTTPure/RouteSpec.purs +++ /dev/null @@ -1,98 +0,0 @@ -module HTTPure.RouteSpec where - -import Prelude (bind, discard, eq, flip, show, ($)) - -import Control.Monad.Eff.Class as EffClass -import Data.Maybe as Maybe -import Node.Encoding as Encoding -import Node.StreamBuffer as StreamBuffer -import Test.Spec as Spec -import Test.Spec.Assertions as Assertions - -import HTTPure.SpecHelpers as SpecHelpers - -import HTTPure.Route as Route - -hooks :: forall e. Route.RouteHooks e -hooks = { body: \_ -> "", headers: \_ -> [], status: \_ -> 200 } - -showSpec :: SpecHelpers.Test -showSpec = Spec.describe "show" do - Spec.describe "with a Get route on /test" $ - Spec.it "is 'GET: /test'" $ - show (Route.Get "/test" hooks) `Assertions.shouldEqual` "GET: /test" - Spec.describe "with a Post route on /test" $ - Spec.it "is 'POST: /test" $ - show (Route.Post "/test" hooks) `Assertions.shouldEqual` "POST: /test" - Spec.describe "with a Put route on /test" $ - Spec.it "is 'PUT /test" $ - show (Route.Put "/test" hooks) `Assertions.shouldEqual` "PUT: /test" - Spec.describe "with a Delete route on /test" $ - Spec.it "is 'DELETE: /test" $ - show (Route.Delete "/test" hooks) `Assertions.shouldEqual` "DELETE: /test" - -eqSpec :: SpecHelpers.Test -eqSpec = Spec.describe "eq" do - Spec.describe "with routes with the same method and same match patterns" $ - Spec.it "is true" $ - route1 `eq` route2 `Assertions.shouldEqual` true - Spec.describe "with routes with different match patterns" $ - Spec.it "is false" $ - route1 `eq` route3 `Assertions.shouldEqual` false - Spec.describe "with routes with different methods" $ - Spec.it "is false" $ - route1 `eq` route4 `Assertions.shouldEqual` false - where - route1 = Route.Get "a" hooks - route2 = Route.Get "a" hooks - route3 = Route.Get "b" hooks - route4 = Route.Put "a" hooks - -runSpec :: SpecHelpers.Test -runSpec = Spec.describe "run" $ - Spec.it "writes the body" do - body <- EffClass.liftEff do - buf <- StreamBuffer.writable - run $ SpecHelpers.mockResponse buf - StreamBuffer.contents Encoding.UTF8 buf - body `Assertions.shouldEqual` "test" - where - run resp = Route.run testRoute (SpecHelpers.mockRequest "/") resp - testRoute = Route.Get "/" - { body: \_ -> "test" - , headers: \_ -> [] - , status: \_ -> 200 - } - -isMatchSpec :: SpecHelpers.Test -isMatchSpec = Spec.describe "isMatch" do - Spec.describe "when the route is a match" $ - Spec.it "is true" $ - isMatch (SpecHelpers.mockRequest "test") `Assertions.shouldEqual` true - Spec.describe "when the route is not a match" $ - Spec.it "is false" $ - isMatch (SpecHelpers.mockRequest "test2") `Assertions.shouldEqual` false - where - isMatch = Route.isMatch route - route = Route.Get "test" hooks - -matchSpec :: SpecHelpers.Test -matchSpec = Spec.describe "match" do - Spec.describe "when a matching route exists" $ - Spec.it "is Just the matching route" $ - match [ route1, route2 ] `Assertions.shouldEqual` Maybe.Just route1 - Spec.describe "when a matching route does not exist" $ - Spec.it "is Nothing" $ - match [ route2 ] `Assertions.shouldEqual` Maybe.Nothing - where - match = (flip Route.match) (SpecHelpers.mockRequest "1") - route1 = Route.Get "1" hooks - route2 = Route.Get "2" hooks - -routeSpec :: SpecHelpers.Test -routeSpec = Spec.describe "Route" do - showSpec - eqSpec - runSpec - isMatchSpec - matchSpec diff --git a/Test/HTTPure/ServerSpec.purs b/Test/HTTPure/ServerSpec.purs index 15338da..f3b8043 100644 --- a/Test/HTTPure/ServerSpec.purs +++ b/Test/HTTPure/ServerSpec.purs @@ -6,54 +6,46 @@ import Control.Monad.Eff.Class as EffClass import Data.Maybe as Maybe import Node.Encoding as Encoding import Node.StreamBuffer as StreamBuffer +import Data.StrMap as StrMap import Test.Spec as Spec import Test.Spec.Assertions as Assertions +import HTTPure.Request as Request +import HTTPure.Response as Response +import HTTPure.Server as Server + import HTTPure.SpecHelpers as SpecHelpers -import HTTPure.Server as Server -import HTTPure.Route as Route - -routes :: forall e. Array (Route.Route e) -routes = - [ Route.Get "/test1" - { status: \_ -> 200 - , headers: \_ -> [] - , body: \_ -> "test1" - } - , Route.Get "/test2" - { status: \_ -> 200 - , headers: \_ -> [] - , body: \_ -> "test2" - } - ] +mockRouter :: forall e. Request.Request -> Response.ResponseM e +mockRouter (Request.Get _ path) = pure $ Response.OK StrMap.empty path +mockRouter _ = pure $ Response.OK StrMap.empty "" handleRequestSpec :: SpecHelpers.Test -handleRequestSpec = Spec.describe "handleRequest" $ - Spec.it "matches and runs a route" do +handleRequestSpec = Spec.describe "handleRequest" do + Spec.it "runs the router and writes the response" do body <- EffClass.liftEff do buf <- StreamBuffer.writable - Server.handleRequest routes mockRequest $ SpecHelpers.mockHTTPResponse buf + Server.handleRequest mockRouter mockRequest $ SpecHelpers.mockResponse buf StreamBuffer.contents Encoding.UTF8 buf body `Assertions.shouldEqual` "test1" where - mockRequest = SpecHelpers.mockHTTPRequest "/test1" + mockRequest = SpecHelpers.mockRequest "GET" "test1" bootSpec :: SpecHelpers.Test -bootSpec = Spec.describe "boot" $ +bootSpec = Spec.describe "boot" do Spec.it "boots a server with the given options" do - EffClass.liftEff $ Server.boot options routes $ pure unit + EffClass.liftEff $ Server.boot options mockRouter $ pure unit out <- SpecHelpers.get "http://localhost:7900/test1" - out `Assertions.shouldEqual` "test1" + out `Assertions.shouldEqual` "/test1" where options = { port: 7900, hostname: "localhost", backlog: Maybe.Nothing } serveSpec :: SpecHelpers.Test -serveSpec = Spec.describe "serve" $ +serveSpec = Spec.describe "serve" do Spec.it "boots a server on the given port" do - EffClass.liftEff $ Server.serve 7901 routes $ pure unit + EffClass.liftEff $ Server.serve 7901 mockRouter $ pure unit out <- SpecHelpers.get "http://localhost:7901/test2" - out `Assertions.shouldEqual` "test2" + out `Assertions.shouldEqual` "/test2" serverSpec :: SpecHelpers.Test serverSpec = Spec.describe "Server" do diff --git a/Test/HTTPure/SpecHelpers.purs b/Test/HTTPure/SpecHelpers.purs index 5dfbb5f..33fd456 100644 --- a/Test/HTTPure/SpecHelpers.purs +++ b/Test/HTTPure/SpecHelpers.purs @@ -1,6 +1,6 @@ module HTTPure.SpecHelpers where -import Prelude (Unit, bind, discard, pure, unit, ($), (<>), (>>=), (<<<)) +import Prelude (Unit, bind, discard, pure, unit, ($), (<>), (>>=)) import Control.Monad.Aff as Aff import Control.Monad.Eff as Eff @@ -15,11 +15,6 @@ import Test.Spec as Spec import Test.Spec.Runner as Runner import Unsafe.Coerce as Coerce -import HTTPure.HTTPureM as HTTPureM -import HTTPure.Request as Request -import HTTPure.Response as Response - - -- | A type alias encapsulating all effect types used in making a mock request. type MockRequestEffects e s = ( st :: ST.ST s @@ -30,11 +25,7 @@ type MockRequestEffects e s = -- | A type alias encapsulating all effect types used in tests. type TestEffects s = Runner.RunnerEffects ( - HTTPureM.HTTPureEffects ( - MockRequestEffects - ( sb :: StreamBuffer.STREAM_BUFFER - ) s - ) + MockRequestEffects ( sb :: StreamBuffer.STREAM_BUFFER ) s ) -- | The type for integration tests. @@ -78,22 +69,12 @@ toString response = Aff.makeAff \_ success -> do get :: forall e s. String -> Aff.Aff (MockRequestEffects e s) String get url = Aff.makeAff (getResponse url) >>= toString --- | Mock a Request object -mockRequest :: forall e. String -> Request.Request e -mockRequest = Request.fromHTTPRequest <<< mockHTTPRequest +-- | Mock an HTTP Request object +mockRequest :: String -> String -> HTTP.Request +mockRequest method url = Coerce.unsafeCoerce { method: method, url: url } --- | Mock a Request object -mockResponse :: forall e1 e2. +-- | Mock an HTTP Request object +mockResponse :: forall e1. Stream.Writable () (sb :: StreamBuffer.STREAM_BUFFER | e1) -> - Response.Response e2 -mockResponse = Response.fromHTTPResponse <<< mockHTTPResponse - --- | Mock an HTTP Request object -mockHTTPRequest :: String -> HTTP.Request -mockHTTPRequest url = Coerce.unsafeCoerce { url: url } - --- | Mock an HTTP Request object -mockHTTPResponse :: forall e1. - Stream.Writable () (sb :: StreamBuffer.STREAM_BUFFER | e1) -> - HTTP.Response -mockHTTPResponse = Coerce.unsafeCoerce + HTTP.Response +mockResponse = Coerce.unsafeCoerce diff --git a/Test/HTTPureSpec.purs b/Test/HTTPureSpec.purs index 84ceada..42b5231 100644 --- a/Test/HTTPureSpec.purs +++ b/Test/HTTPureSpec.purs @@ -6,19 +6,24 @@ import Test.Spec as Spec import Test.Spec.Reporter as Reporter import Test.Spec.Runner as Runner +import HTTPure.BodySpec as BodySpec +import HTTPure.HeadersSpec as HeadersSpec import HTTPure.HTTPureMSpec as HTTPureMSpec +import HTTPure.PathSpec as PathSpec import HTTPure.RequestSpec as RequestSpec import HTTPure.ResponseSpec as ResponseSpec -import HTTPure.RouteSpec as RouteSpec import HTTPure.ServerSpec as ServerSpec -import HTTPure.SpecHelpers as SpecHelpers import HTTPure.IntegrationSpec as IntegrationSpec +import HTTPure.SpecHelpers as SpecHelpers + main :: SpecHelpers.TestSuite main = Runner.run [ Reporter.specReporter ] $ Spec.describe "HTTPure" do + BodySpec.bodySpec + HeadersSpec.headersSpec HTTPureMSpec.httpureMSpec + PathSpec.pathSpec RequestSpec.requestSpec ResponseSpec.responseSpec - RouteSpec.routeSpec ServerSpec.serverSpec IntegrationSpec.integrationSpec diff --git a/bower.json b/bower.json index 3c81b24..6f405e0 100644 --- a/bower.json +++ b/bower.json @@ -9,9 +9,12 @@ }, "ignore": [ "**/.*", + "Documentation", "Output", "Test", - "bower.json" + "Makefile", + "*.json", + "*.md" ], "dependencies": { "purescript-prelude": "^3.0.0",