Reexport routing-duplex to simplify imports
This commit is contained in:
parent
52ceb844a7
commit
f3837b0563
28
Readme.md
28
Readme.md
@ -29,17 +29,13 @@ module Main where
|
||||
import Prelude hiding ((/))
|
||||
|
||||
import Data.Generic.Rep (class Generic)
|
||||
import HTTPurple (ServerM, ok, serve)
|
||||
import Routing.Duplex (RouteDuplex', root, segment)
|
||||
import Routing.Duplex.Generic (sum)
|
||||
import Routing.Duplex.Generic.Syntax ((/))
|
||||
import HTTPurple
|
||||
|
||||
data Route = Hello String
|
||||
|
||||
derive instance Generic Route _
|
||||
|
||||
route :: RouteDuplex' Route
|
||||
route = root $ sum
|
||||
route = mkRoute
|
||||
{ "Hello": "hello" / segment
|
||||
}
|
||||
|
||||
@ -129,21 +125,16 @@ import Data.Either (Either(..))
|
||||
import Data.Generic.Rep (class Generic)
|
||||
import Data.Maybe (Maybe(..))
|
||||
import Data.Tuple (Tuple(..))
|
||||
import HTTPurple (ServerM, found', headers, ok, serve)
|
||||
import Routing.Duplex (RouteDuplex', as, optional, print, root, segment, string)
|
||||
import Routing.Duplex.Generic as G
|
||||
import Routing.Duplex.Generic.Syntax ((/), (?))
|
||||
import HTTPurple
|
||||
|
||||
data Route
|
||||
= Home
|
||||
| Profile String
|
||||
| Account String
|
||||
| Search { q :: String, sorting :: Maybe Sort }
|
||||
|
||||
derive instance Generic Route _
|
||||
|
||||
data Sort = Asc | Desc
|
||||
|
||||
derive instance Generic Sort _
|
||||
|
||||
sortToString :: Sort -> String
|
||||
@ -161,8 +152,8 @@ sort :: RouteDuplex' String -> RouteDuplex' Sort
|
||||
sort = as sortToString sortFromString
|
||||
|
||||
api :: RouteDuplex' Route
|
||||
api = root $ G.sum
|
||||
{ "Home": G.noArgs
|
||||
api = root $ sum
|
||||
{ "Home": noArgs
|
||||
, "Profile": "profile" / string segment
|
||||
, "Account": "account" / string segment
|
||||
, "Search": "search" ? { q: string, sorting: optional <<< sort }
|
||||
@ -173,11 +164,12 @@ main = serve { port: 8080 } { route: api, router: apiRouter }
|
||||
where
|
||||
|
||||
apiRouter { route: Home } = ok "hello world!"
|
||||
apiRouter { route: (Profile profile) } = ok $ "hello " <> profile <> "!"
|
||||
apiRouter { route: (Account account) } = found' redirect ""
|
||||
apiRouter { route: Profile profile } = ok $ "hello " <> profile <> "!"
|
||||
apiRouter { route: Account account } = found' redirect ""
|
||||
where
|
||||
redirect = headers [ Tuple "Location" $ print api $ Profile account ]
|
||||
apiRouter { route: (Search { q, sorting }) } = ok $ "searching for query " <> q <> " " <> case sorting of
|
||||
reverseRoute = print api $ Profile account
|
||||
redirect = headers [ Tuple "Location" reverseRoute ]
|
||||
apiRouter { route: Search { q, sorting } } = ok $ "searching for query " <> q <> " " <> case sorting of
|
||||
Just Asc -> "ascending"
|
||||
Just Desc -> "descending"
|
||||
Nothing -> "defaulting to ascending"
|
||||
|
@ -10,6 +10,9 @@ module HTTPurple
|
||||
, module HTTPurple.Response
|
||||
, module HTTPurple.Server
|
||||
, module HTTPurple.Status
|
||||
, module Routing.Duplex
|
||||
, module Routing.Duplex.Generic
|
||||
, module Routing.Duplex.Generic.Syntax
|
||||
) where
|
||||
|
||||
import HTTPurple.Body (toBuffer, toStream, toString)
|
||||
@ -20,6 +23,9 @@ import HTTPurple.Path (Path)
|
||||
import HTTPurple.Query (Query)
|
||||
import HTTPurple.Request (Request, fullPath)
|
||||
import HTTPurple.Response (Response, ResponseM, accepted, accepted', alreadyReported, alreadyReported', badGateway, badGateway', badRequest, badRequest', conflict, conflict', continue, continue', created, created', emptyResponse, emptyResponse', expectationFailed, expectationFailed', failedDependency, failedDependency', forbidden, forbidden', found, found', gatewayTimeout, gatewayTimeout', gone, gone', hTTPVersionNotSupported, hTTPVersionNotSupported', iMUsed, iMUsed', imATeapot, imATeapot', insufficientStorage, insufficientStorage', internalServerError, internalServerError', lengthRequired, lengthRequired', locked, locked', loopDetected, loopDetected', methodNotAllowed, methodNotAllowed', misdirectedRequest, misdirectedRequest', movedPermanently, movedPermanently', multiStatus, multiStatus', multipleChoices, multipleChoices', networkAuthenticationRequired, networkAuthenticationRequired', noContent, noContent', nonAuthoritativeInformation, nonAuthoritativeInformation', notAcceptable, notAcceptable', notExtended, notExtended', notFound, notFound', notImplemented, notImplemented', notModified, notModified', ok, ok', partialContent, partialContent', payloadTooLarge, payloadTooLarge', paymentRequired, paymentRequired', permanentRedirect, permanentRedirect', preconditionFailed, preconditionFailed', preconditionRequired, preconditionRequired', processing, processing', proxyAuthenticationRequired, proxyAuthenticationRequired', rangeNotSatisfiable, rangeNotSatisfiable', requestHeaderFieldsTooLarge, requestHeaderFieldsTooLarge', requestTimeout, requestTimeout', resetContent, resetContent', response, response', seeOther, seeOther', serviceUnavailable, serviceUnavailable', switchingProtocols, switchingProtocols', temporaryRedirect, temporaryRedirect', tooManyRequests, tooManyRequests', uRITooLong, uRITooLong', unauthorized, unauthorized', unavailableForLegalReasons, unavailableForLegalReasons', unprocessableEntity, unprocessableEntity', unsupportedMediaType, unsupportedMediaType', upgradeRequired, upgradeRequired', useProxy, useProxy', variantAlsoNegotiates, variantAlsoNegotiates')
|
||||
import HTTPurple.Routes (type (<+>), combineRoutes, orElse, (<+>))
|
||||
import HTTPurple.Routes (type (<+>), combineRoutes, orElse, (<+>), mkRoute)
|
||||
import HTTPurple.Server (ServerM, serve)
|
||||
import HTTPurple.Status (Status)
|
||||
import Routing.Duplex (class RouteDuplexBuildParams, class RouteDuplexParams, RouteDuplex(..), RouteDuplex', as, boolean, buildParams, default, end, flag, int, many, many1, optional, param, params, parse, path, prefix, print, prop, record, rest, root, segment, string, suffix, (:=))
|
||||
import Routing.Duplex.Generic (noArgs, product, sum, (~), class GRouteDuplex, class GRouteDuplexCtr)
|
||||
import Routing.Duplex.Generic.Syntax (gsep, (/), gparams, (?))
|
||||
|
@ -1,6 +1,7 @@
|
||||
module HTTPurple.Routes
|
||||
( (<+>)
|
||||
, combineRoutes
|
||||
, mkRoute
|
||||
, orElse
|
||||
, type (<+>)
|
||||
) where
|
||||
@ -9,11 +10,13 @@ import Prelude
|
||||
|
||||
import Control.Alt ((<|>))
|
||||
import Data.Either (Either(..))
|
||||
import Data.Generic.Rep (class Generic)
|
||||
import Data.Profunctor.Choice ((|||))
|
||||
import HTTPurple.Request (Request)
|
||||
import HTTPurple.Response (ResponseM)
|
||||
import Record as Record
|
||||
import Routing.Duplex as RD
|
||||
import Routing.Duplex.Generic as RG
|
||||
import Type.Proxy (Proxy(..))
|
||||
|
||||
infixr 0 type Either as <+>
|
||||
@ -39,3 +42,10 @@ orElse ::
|
||||
orElse leftRouter _ request@{ route: Left l } = leftRouter $ Record.set (Proxy :: _ "route") l request
|
||||
orElse _ rightRouter request@{ route: Right r } = rightRouter $ Record.set (Proxy :: _ "route") r request
|
||||
|
||||
mkRoute ::
|
||||
forall i iGen r.
|
||||
Generic i iGen =>
|
||||
RG.GRouteDuplex iGen r =>
|
||||
Record r ->
|
||||
RD.RouteDuplex i i
|
||||
mkRoute = RD.root <<< RG.sum
|
||||
|
Loading…
Reference in New Issue
Block a user