@@ -10,11 +10,8 @@ module Examples.AuthenticationAndAuthorization where
1010import Prelude
1111
1212import Control.IxMonad ((:>>=), (:*>))
13- import Control.Monad.Aff.AVar (AVAR )
14- import Control.Monad.Aff.Class (class MonadAff )
15- import Control.Monad.Eff (Eff )
16- import Control.Monad.Eff.Console (CONSOLE )
17- import Control.Monad.Eff.Exception (EXCEPTION )
13+ import Effect.Aff.Class (class MonadAff )
14+ import Effect (Effect )
1815import Data.Either (Either (..))
1916import Data.HTTP.Method (Method (GET))
2017import Data.Maybe (Maybe (Nothing, Just))
@@ -29,8 +26,6 @@ import Hyper.Node.Server (defaultOptionsWithLogging, runServer)
2926import Hyper.Request (class Request , getRequestData )
3027import Hyper.Response (class Response , class ResponseWritable , ResponseEnded , StatusLineOpen , closeHeaders , contentType , respond , writeStatus )
3128import Hyper.Status (Status , statusNotFound , statusOK )
32- import Node.Buffer (BUFFER )
33- import Node.HTTP (HTTP )
3429import Text.Smolder.HTML (a , h1 , li , p , section , ul )
3530import Text.Smolder.HTML.Attributes as A
3631import Text.Smolder.Markup (Markup , text , (!))
@@ -130,7 +125,7 @@ adminHandler =
130125-- This could be a function checking the username/password in a database
131126-- in your application.
132127userFromBasicAuth
133- :: forall m e . MonadAff e m =>
128+ :: forall m . MonadAff m =>
134129 Tuple String String
135130 -> m (Maybe User )
136131userFromBasicAuth =
@@ -155,8 +150,8 @@ getAdminRole conn =
155150 _ -> pure Nothing
156151
157152
158- app :: forall m e req res b c
159- . MonadAff ( buffer :: BUFFER | e ) m
153+ app :: forall m req res b c
154+ . MonadAff m
160155 => Request req m
161156 => Response res m b
162157 => ResponseWritable b m String
@@ -204,7 +199,7 @@ app = BasicAuth.withAuthentication userFromBasicAuth :>>= \_ → router
204199 _, _ ->
205200 notFound
206201
207- main :: forall e . Eff ( http :: HTTP , console :: CONSOLE , exception :: EXCEPTION , avar :: AVAR , buffer :: BUFFER | e ) Unit
202+ main :: Effect Unit
208203main =
209204 let
210205 components = { authentication: unit
0 commit comments