#22 add support for writing headers and status (#32)

* Add support for writing status code

* Add support for writing headers

* Code cleanup
This commit is contained in:
Connor Prussin 2017-07-17 16:42:13 -07:00 committed by GitHub
parent 9e91350de1
commit 44df22e331
19 changed files with 267 additions and 55 deletions

View File

@ -0,0 +1,29 @@
module Headers where
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
port :: Int
port = 8082
-- | Shortcut for `show port`
portS :: String
portS = show port
-- | Say 'hello world!' when run
sayHello :: forall e. HTTPure.Request -> HTTPure.ResponseM e
sayHello _ = pure $ HTTPure.OK (StrMap.singleton "X-Example" "hello world!") ""
-- | Boot up the server
main :: forall e. HTTPure.ServerM (console :: Console.CONSOLE | e)
main = HTTPure.serve port sayHello do
Console.log $ " ┌──────────────────────────────────────────────────────────────┐"
Console.log $ " │ Server now up on port " <> portS <> ""
Console.log $ " │ │"
Console.log $ " │ To test, run: │"
Console.log $ " │ > curl -v localhost:" <> portS <> " # => ... X-Example: hello world! │"
Console.log $ " └──────────────────────────────────────────────────────────────┘"

View File

@ -0,0 +1,10 @@
# Headers Example
This is a basic example of working with headers. It will return the 'X-Example'
response header with the value 'hello world!'.
To run the example server, run:
```bash
make example EXAMPLE=Headers
```

View File

@ -21,7 +21,6 @@ sayHello _ = pure $ HTTPure.OK StrMap.empty "hello world!"
-- | Boot up the server -- | Boot up the server
main :: forall e. HTTPure.ServerM (console :: Console.CONSOLE | e) main :: forall e. HTTPure.ServerM (console :: Console.CONSOLE | e)
main = HTTPure.serve port sayHello do main = HTTPure.serve port sayHello do
Console.log $ ""
Console.log $ " ┌────────────────────────────────────────────┐" Console.log $ " ┌────────────────────────────────────────────┐"
Console.log $ " │ Server now up on port " <> portS <> "" Console.log $ " │ Server now up on port " <> portS <> ""
Console.log $ " │ │" Console.log $ " │ │"

View File

@ -23,7 +23,6 @@ router _ = pure $ HTTPure.OK StrMap.empty ""
-- | Boot up the server -- | Boot up the server
main :: forall e. HTTPure.ServerM (console :: Console.CONSOLE | e) main :: forall e. HTTPure.ServerM (console :: Console.CONSOLE | e)
main = HTTPure.serve port router do main = HTTPure.serve port router do
Console.log $ ""
Console.log $ " ┌───────────────────────────────────────────────┐" Console.log $ " ┌───────────────────────────────────────────────┐"
Console.log $ " │ Server now up on port " <> portS <> "" Console.log $ " │ Server now up on port " <> portS <> ""
Console.log $ " │ │" Console.log $ " │ │"

View File

@ -1,7 +1,26 @@
module HTTPure.Body module HTTPure.Body
( Body ( Body
, write
) where ) where
import Prelude (Unit, bind, discard, pure, unit)
import Node.Encoding as Encoding
import Node.HTTP as HTTP
import Node.Stream as Stream
import HTTPure.HTTPureM as HTTPureM
-- | The Body type is just sugar for a String, that will be sent or received in -- | The Body type is just sugar for a String, that will be sent or received in
-- | the HTTP body. -- | the HTTP body.
type Body = String type Body = String
-- | Write a body to the given HTTP Response and close it.
write :: forall e. HTTP.Response -> Body -> HTTPureM.HTTPureM e Unit
write response body = do
_ <- Stream.writeString stream Encoding.UTF8 body noop
Stream.end stream noop
noop
where
stream = HTTP.responseAsStream response
noop = pure unit

View File

@ -1,9 +1,26 @@
module HTTPure.Headers module HTTPure.Headers
( Headers ( Headers
, write
) where ) where
import Prelude (Unit, bind, pure, unit, ($))
import Data.Maybe as Maybe
import Data.StrMap as StrMap import Data.StrMap as StrMap
import Data.Traversable as Traversable
import Node.HTTP as HTTP
import HTTPure.HTTPureM as HTTPureM
-- | The Headers type is just sugar for a StrMap of Strings that represents the -- | 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. -- | set of headers sent or received in an HTTP request or response.
type Headers = StrMap.StrMap String type Headers = StrMap.StrMap String
-- | Write a set of headers to the given HTTP Response.
write :: forall e. HTTP.Response -> Headers -> HTTPureM.HTTPureM e Unit
write response headers = do
_ <- Traversable.traverse writeHeader $ StrMap.keys headers
pure unit
where
getHeader header = Maybe.fromMaybe "" $ StrMap.lookup header headers
writeHeader header = HTTP.setHeader response header $ getHeader header

View File

@ -4,15 +4,15 @@ module HTTPure.Response
, send , send
) where ) where
import Prelude (Unit, bind, discard, pure, unit) import Prelude (Unit, discard, ($))
import Node.Encoding as Encoding import Data.Maybe as Maybe
import Node.HTTP as HTTP import Node.HTTP as HTTP
import Node.Stream as Stream
import HTTPure.Body as Body import HTTPure.Body as Body
import HTTPure.Headers as Headers import HTTPure.Headers as Headers
import HTTPure.HTTPureM as HTTPureM import HTTPure.HTTPureM as HTTPureM
import HTTPure.Status as Status
-- | A response is a status, and can have headers and a body. Different response -- | A response is a status, and can have headers and a body. Different response
-- | codes will allow different response components to be sent. -- | codes will allow different response components to be sent.
@ -24,14 +24,20 @@ data Response
-- | methods. -- | methods.
type ResponseM e = HTTPureM.HTTPureM e Response type ResponseM e = HTTPureM.HTTPureM e Response
-- | Send a status, headers, and body to a HTTP response.
send' :: forall e.
HTTP.Response ->
Status.Status ->
Headers.Headers ->
Maybe.Maybe Body.Body ->
HTTPureM.HTTPureM e Unit
send' response status headers body = do
Status.write response status
Headers.write response headers
Body.write response $ Maybe.fromMaybe "" body
-- | Given an HTTP response and a HTTPure response, this method will return a -- | Given an HTTP response and a HTTPure response, this method will return a
-- | monad encapsulating writing the HTTPure response to the HTTP response and -- | monad encapsulating writing the HTTPure response to the HTTP response and
-- | closing the HTTP response. -- | closing the HTTP response.
send :: forall e. HTTP.Response -> Response -> HTTPureM.HTTPureM e Unit send :: forall e. HTTP.Response -> Response -> HTTPureM.HTTPureM e Unit
send response (OK headers body) = do send response (OK headers body) = send' response 200 headers (Maybe.Just body)
_ <- Stream.writeString stream Encoding.UTF8 body noop
Stream.end stream noop
noop
where
stream = HTTP.responseAsStream response
noop = pure unit

View File

@ -0,0 +1,17 @@
module HTTPure.Status
( Status
, write
) where
import Prelude (Unit)
import Node.HTTP as HTTP
import HTTPure.HTTPureM as HTTPureM
-- | The Status type enumerates all valid HTTP response status codes.
type Status = Int
-- | Write a status to a given HTTP Response.
write :: forall e. HTTP.Response -> Status -> HTTPureM.HTTPureM e Unit
write = HTTP.setStatusCode

View File

@ -12,7 +12,6 @@ NPM := npm
# Package manifest files # Package manifest files
BOWERJSON := bower.json BOWERJSON := bower.json
PACKAGEJSON := package.json
# Various input directories # Various input directories
SRCPATH := ./Library SRCPATH := ./Library
@ -25,7 +24,6 @@ EXAMPLEPATH := $(EXAMPLESPATH)/$(EXAMPLE)
# Various output directories # Various output directories
BUILD := $(OUTPUT)/Build BUILD := $(OUTPUT)/Build
COMPONENTS := $(OUTPUT)/Components COMPONENTS := $(OUTPUT)/Components
MODULES := $(OUTPUT)/node_modules
OUTPUT_DOCS := $(OUTPUT)/Documentation OUTPUT_DOCS := $(OUTPUT)/Documentation
OUTPUT_EXAMPLE := $(OUTPUT)/Examples/$(EXAMPLE) OUTPUT_EXAMPLE := $(OUTPUT)/Examples/$(EXAMPLE)
@ -40,16 +38,12 @@ EXAMPLESOURCES := $(EXAMPLESPATH)/**/*
# This is the module name for the entry point for the test suite # This is the module name for the entry point for the test suite
TESTMAIN := HTTPure.HTTPureSpec TESTMAIN := HTTPure.HTTPureSpec
$(MODULES): $(PACKAGEJSON)
$(NPM) install
mv node_modules $(MODULES)
# Install bower components # Install bower components
$(COMPONENTS): $(BOWERJSON) $(COMPONENTS): $(BOWERJSON)
$(BOWER) install $(BOWER) install
# Build the source files # Build the source files
$(BUILD): $(COMPONENTS) $(MODULES) $(SOURCES) $(BUILD): $(COMPONENTS) $(SOURCES)
$(PULP) build \ $(PULP) build \
--src-path $(SRCPATH) \ --src-path $(SRCPATH) \
--build-path $(BUILD) --build-path $(BUILD)
@ -92,7 +86,7 @@ test: $(BUILD) $(TESTSOURCES) $(EXAMPLESOURCES)
--main $(TESTMAIN) --main $(TESTMAIN)
# Launch a repl with all modules loaded # Launch a repl with all modules loaded
repl: $(COMPONENTS) $(MODULES) $(SOURCES) $(TESTSOURCES) $(EXAMPLESOURCES) repl: $(COMPONENTS) $(SOURCES) $(TESTSOURCES) $(EXAMPLESOURCES)
$(PULP) repl \ $(PULP) repl \
--include $(EXAMPLESPATH) \ --include $(EXAMPLESPATH) \
--src-path $(SRCPATH) \ --src-path $(SRCPATH) \
@ -116,7 +110,7 @@ help:
$(info - make help Print this help) $(info - make help Print this help)
# Build the documentation # Build the documentation
$(OUTPUT_DOCS): $(COMPONENTS) $(MODULES) $(SOURCES) $(OUTPUT_DOCS): $(COMPONENTS) $(SOURCES)
$(PULP) docs \ $(PULP) docs \
--src-path $(SRCPATH) --src-path $(SRCPATH)
rm -rf $(OUTPUT_DOCS) rm -rf $(OUTPUT_DOCS)

View File

@ -1,11 +1,24 @@
module HTTPure.BodySpec where module HTTPure.BodySpec where
import Prelude (pure, unit) import Prelude (bind, discard, pure, ($))
import Control.Monad.Eff.Class as EffClass
import Test.Spec as Spec import Test.Spec as Spec
import Test.Spec.Assertions as Assertions
import HTTPure.Body as Body
import HTTPure.SpecHelpers as SpecHelpers import HTTPure.SpecHelpers as SpecHelpers
writeSpec :: SpecHelpers.Test
writeSpec = Spec.describe "write" do
Spec.it "writes the string to the Response body" do
body <- EffClass.liftEff do
resp <- SpecHelpers.mockResponse
Body.write resp "test"
pure $ SpecHelpers.getResponseBody resp
body `Assertions.shouldEqual` "test"
bodySpec :: SpecHelpers.Test bodySpec :: SpecHelpers.Test
bodySpec = Spec.describe "Body" do bodySpec = Spec.describe "Body" do
pure unit writeSpec

View File

@ -1,11 +1,25 @@
module HTTPure.HeadersSpec where module HTTPure.HeadersSpec where
import Prelude (pure, unit) import Prelude (bind, discard, pure, ($))
import Control.Monad.Eff.Class as EffClass
import Data.StrMap as StrMap
import Test.Spec as Spec import Test.Spec as Spec
import Test.Spec.Assertions as Assertions
import HTTPure.Headers as Headers
import HTTPure.SpecHelpers as SpecHelpers import HTTPure.SpecHelpers as SpecHelpers
writeSpec :: SpecHelpers.Test
writeSpec = Spec.describe "write" do
Spec.it "writes the headers to the response" do
header <- EffClass.liftEff do
mock <- SpecHelpers.mockResponse
Headers.write mock $ StrMap.singleton "X-Test" "test"
pure $ SpecHelpers.getResponseHeader "X-Test" mock
header `Assertions.shouldEqual` "test"
headersSpec :: SpecHelpers.Test headersSpec :: SpecHelpers.Test
headersSpec = Spec.describe "Headers" do headersSpec = Spec.describe "Headers" do
pure unit writeSpec

View File

@ -10,6 +10,7 @@ import HTTPure.SpecHelpers as SpecHelpers
import HelloWorld as HelloWorld import HelloWorld as HelloWorld
import MultiRoute as MultiRoute import MultiRoute as MultiRoute
import Headers as Headers
helloWorldSpec :: SpecHelpers.Test helloWorldSpec :: SpecHelpers.Test
helloWorldSpec = Spec.it "runs the hello world example" do helloWorldSpec = Spec.it "runs the hello world example" do
@ -25,7 +26,14 @@ multiRouteSpec = Spec.it "runs the multi route example" do
goodbye <- SpecHelpers.get "http://localhost:8081/goodbye" goodbye <- SpecHelpers.get "http://localhost:8081/goodbye"
goodbye `Assertions.shouldEqual` "goodbye" goodbye `Assertions.shouldEqual` "goodbye"
headersSpec :: SpecHelpers.Test
headersSpec = Spec.it "runs the headers example" do
EffClass.liftEff Headers.main
header <- SpecHelpers.getHeader "http://localhost:8082" "X-Example"
header `Assertions.shouldEqual` "hello world!"
integrationSpec :: SpecHelpers.Test integrationSpec :: SpecHelpers.Test
integrationSpec = Spec.describe "Integration" do integrationSpec = Spec.describe "Integration" do
helloWorldSpec helloWorldSpec
multiRouteSpec multiRouteSpec
headersSpec

View File

@ -1,11 +1,9 @@
module HTTPure.ResponseSpec where module HTTPure.ResponseSpec where
import Prelude (bind, discard, ($)) import Prelude (bind, discard, pure, ($))
import Control.Monad.Eff.Class as EffClass import Control.Monad.Eff.Class as EffClass
import Data.StrMap as StrMap import Data.StrMap as StrMap
import Node.Encoding as Encoding
import Node.StreamBuffer as StreamBuffer
import Test.Spec as Spec import Test.Spec as Spec
import Test.Spec.Assertions as Assertions import Test.Spec.Assertions as Assertions
@ -16,13 +14,23 @@ import HTTPure.SpecHelpers as SpecHelpers
sendSpec :: SpecHelpers.Test sendSpec :: SpecHelpers.Test
sendSpec = Spec.describe "send" do sendSpec = Spec.describe "send" do
Spec.describe "with an OK" do Spec.describe "with an OK" do
Spec.pending "writes the headers" Spec.it "writes the headers" do
header <- EffClass.liftEff do
resp <- SpecHelpers.mockResponse
Response.send resp $ Response.OK (StrMap.singleton "X-Test" "test") ""
pure $ SpecHelpers.getResponseHeader "X-Test" resp
header `Assertions.shouldEqual` "test"
Spec.it "writes the status" do
status <- EffClass.liftEff do
resp <- SpecHelpers.mockResponse
Response.send resp $ Response.OK StrMap.empty ""
pure $ SpecHelpers.getResponseStatus resp
status `Assertions.shouldEqual` 200
Spec.it "writes the body" do Spec.it "writes the body" do
body <- EffClass.liftEff do body <- EffClass.liftEff do
buf <- StreamBuffer.writable resp <- SpecHelpers.mockResponse
let resp = SpecHelpers.mockResponse buf
Response.send resp $ Response.OK StrMap.empty "test" Response.send resp $ Response.OK StrMap.empty "test"
StreamBuffer.contents Encoding.UTF8 buf pure $ SpecHelpers.getResponseBody resp
body `Assertions.shouldEqual` "test" body `Assertions.shouldEqual` "test"
responseSpec :: SpecHelpers.Test responseSpec :: SpecHelpers.Test

View File

@ -0,0 +1,19 @@
"use strict";
exports.mockResponse = function() {
return {
body: "",
headers: {},
write: function(str) {
this.body = this.body + str;
},
end: function() {
},
setHeader: function(header, val) {
this.headers[header] = val;
}
};
};

View File

@ -1,16 +1,18 @@
module HTTPure.SpecHelpers where 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.Aff as Aff
import Control.Monad.Eff as Eff import Control.Monad.Eff as Eff
import Control.Monad.Eff.Exception as Exception import Control.Monad.Eff.Exception as Exception
import Control.Monad.ST as ST import Control.Monad.ST as ST
import Data.Maybe as Maybe
import Data.String as StringUtil
import Data.StrMap as StrMap
import Node.Encoding as Encoding import Node.Encoding as Encoding
import Node.HTTP as HTTP import Node.HTTP as HTTP
import Node.HTTP.Client as HTTPClient import Node.HTTP.Client as HTTPClient
import Node.Stream as Stream import Node.Stream as Stream
import Node.StreamBuffer as StreamBuffer
import Test.Spec as Spec import Test.Spec as Spec
import Test.Spec.Runner as Runner import Test.Spec.Runner as Runner
import Unsafe.Coerce as Coerce import Unsafe.Coerce as Coerce
@ -19,14 +21,18 @@ import Unsafe.Coerce as Coerce
type MockRequestEffects e s = type MockRequestEffects e s =
( st :: ST.ST s ( st :: ST.ST s
, exception :: Exception.EXCEPTION , exception :: Exception.EXCEPTION
, http :: HTTP.HTTP | e , http :: HTTP.HTTP
| e
)
type MockResponseEffects e =
( mockResponse :: MOCK_RESPONSE
| e
) )
-- | A type alias encapsulating all effect types used in tests. -- | A type alias encapsulating all effect types used in tests.
type TestEffects s = type TestEffects s =
Runner.RunnerEffects ( Runner.RunnerEffects (MockRequestEffects (MockResponseEffects ()) s)
MockRequestEffects ( sb :: StreamBuffer.STREAM_BUFFER ) s
)
-- | The type for integration tests. -- | The type for integration tests.
type Test = forall s. Spec.Spec (TestEffects s) Unit type Test = forall s. Spec.Spec (TestEffects s) Unit
@ -44,10 +50,9 @@ endRequest request = Stream.end (HTTPClient.requestAsStream request) $ pure unit
-- | client request. -- | client request.
getResponse :: forall e. getResponse :: forall e.
String -> String ->
(Exception.Error -> Eff.Eff (http :: HTTP.HTTP | e) Unit) -> Aff.Aff (http :: HTTP.HTTP | e) HTTPClient.Response
(HTTPClient.Response -> Eff.Eff (http :: HTTP.HTTP | e) Unit) -> getResponse url = Aff.makeAff \_ success ->
Eff.Eff (http :: HTTP.HTTP | e) Unit HTTPClient.requestFromURI url success >>= endRequest
getResponse url _ success = HTTPClient.requestFromURI url success >>= endRequest
-- | Given an ST String buffer and a new string, concatenate that new string -- | Given an ST String buffer and a new string, concatenate that new string
-- | onto the ST buffer. -- | onto the ST buffer.
@ -67,14 +72,49 @@ toString response = Aff.makeAff \_ success -> do
-- | Run an HTTP GET with the given url and return an Aff that contains the -- | Run an HTTP GET with the given url and return an Aff that contains the
-- | string with the response body. -- | string with the response body.
get :: forall e s. String -> Aff.Aff (MockRequestEffects e s) String get :: forall e s. String -> Aff.Aff (MockRequestEffects e s) String
get url = Aff.makeAff (getResponse url) >>= toString get url = getResponse url >>= toString
-- | Convert a request to an Aff containing the string with the given header
-- | value.
extractHeader :: String -> HTTPClient.Response -> String
extractHeader header = unmaybe <<< lookup <<< HTTPClient.responseHeaders
where
unmaybe = Maybe.fromMaybe ""
lookup = StrMap.lookup $ StringUtil.toLower header
-- | Run an HTTP GET with the given url and return an Aff that contains the
-- | string with the header value for the given header.
getHeader :: forall e s.
String ->
String ->
Aff.Aff (MockRequestEffects e s) String
getHeader url header = extractHeader header <$> getResponse url
-- | Mock an HTTP Request object -- | Mock an HTTP Request object
mockRequest :: String -> String -> HTTP.Request mockRequest :: String -> String -> HTTP.Request
mockRequest method url = Coerce.unsafeCoerce { method: method, url: url } mockRequest method url = Coerce.unsafeCoerce { method: method, url: url }
-- | Mock an HTTP Request object -- | An effect encapsulating creating a mock response object
mockResponse :: forall e1. foreign import data MOCK_RESPONSE :: Eff.Effect
Stream.Writable () (sb :: StreamBuffer.STREAM_BUFFER | e1) ->
HTTP.Response -- | Mock an HTTP Response object
mockResponse = Coerce.unsafeCoerce foreign import mockResponse ::
forall e. Eff.Eff (mockResponse :: MOCK_RESPONSE | e) HTTP.Response
-- | Get the current body from an HTTP Response object (note this will only work
-- | with an object returned from mockResponse).
getResponseBody :: HTTP.Response -> String
getResponseBody = _.body <<< Coerce.unsafeCoerce
-- | Get the currently set status from an HTTP Response object.
getResponseStatus :: HTTP.Response -> Int
getResponseStatus = _.statusCode <<< Coerce.unsafeCoerce
-- | Get all current headers on the HTTP Response object.
getResponseHeaders :: HTTP.Response -> StrMap.StrMap String
getResponseHeaders = Coerce.unsafeCoerce <<< _.headers <<< Coerce.unsafeCoerce
-- | Get the current value for the header on the HTTP Response object.
getResponseHeader :: String -> HTTP.Response -> String
getResponseHeader header =
Maybe.fromMaybe "" <<< StrMap.lookup header <<< getResponseHeaders

View File

@ -0,0 +1,24 @@
module HTTPure.StatusSpec where
import Prelude (bind, discard, pure, ($))
import Control.Monad.Eff.Class as EffClass
import Test.Spec as Spec
import Test.Spec.Assertions as Assertions
import HTTPure.Status as Status
import HTTPure.SpecHelpers as SpecHelpers
writeSpec :: SpecHelpers.Test
writeSpec = Spec.describe "write" do
Spec.it "writes the given status code" do
status <- EffClass.liftEff do
mock <- SpecHelpers.mockResponse
Status.write mock 123
pure $ SpecHelpers.getResponseStatus mock
status `Assertions.shouldEqual` 123
statusSpec :: SpecHelpers.Test
statusSpec = Spec.describe "Status" do
writeSpec

View File

@ -13,6 +13,7 @@ import HTTPure.PathSpec as PathSpec
import HTTPure.RequestSpec as RequestSpec import HTTPure.RequestSpec as RequestSpec
import HTTPure.ResponseSpec as ResponseSpec import HTTPure.ResponseSpec as ResponseSpec
import HTTPure.ServerSpec as ServerSpec import HTTPure.ServerSpec as ServerSpec
import HTTPure.StatusSpec as StatusSpec
import HTTPure.IntegrationSpec as IntegrationSpec import HTTPure.IntegrationSpec as IntegrationSpec
import HTTPure.SpecHelpers as SpecHelpers import HTTPure.SpecHelpers as SpecHelpers
@ -26,4 +27,5 @@ main = Runner.run [ Reporter.specReporter ] $ Spec.describe "HTTPure" do
RequestSpec.requestSpec RequestSpec.requestSpec
ResponseSpec.responseSpec ResponseSpec.responseSpec
ServerSpec.serverSpec ServerSpec.serverSpec
StatusSpec.statusSpec
IntegrationSpec.integrationSpec IntegrationSpec.integrationSpec

View File

@ -23,7 +23,6 @@
"devDependencies": { "devDependencies": {
"purescript-psci-support": "^3.0.0", "purescript-psci-support": "^3.0.0",
"purescript-spec": "^1.0.0", "purescript-spec": "^1.0.0",
"purescript-unsafe-coerce": "^3.0.0", "purescript-unsafe-coerce": "^3.0.0"
"purescript-node-stream-buffers": "^0.1.0"
} }
} }

View File

@ -1,5 +0,0 @@
{
"devDependencies": {
"stream-buffers": "^3.0.1"
}
}