Small haddocks changes for authentication

This commit is contained in:
aaron levin 2015-08-12 20:20:18 -04:00 committed by Arian van Putten
parent 77d366c189
commit 873f79ef79
2 changed files with 12 additions and 20 deletions

View file

@ -1,19 +1,14 @@
{-# LANGUAGE DataKinds #-} -- | An example of a custom authentication framework that checks a Cookie for a
{-# LANGUAGE DeriveGeneric #-} -- value.
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE DataKinds #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE DeriveGeneric #-}
{-# LANGUAGE TypeOperators #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
import Data.Aeson
import Data.ByteString (ByteString)
import Data.Text (Text)
import GHC.Generics
import Network.HTTP.Types
import Network.Wai
import Network.Wai.Handler.Warp
import Servant
import Servant.Server.Internal
import Data.Aeson import Data.Aeson
import Data.ByteString (ByteString) import Data.ByteString (ByteString)
import Data.ByteString.Builder.Internal (byteStringCopy) import Data.ByteString.Builder.Internal (byteStringCopy)
@ -28,9 +23,6 @@ import Servant.API.Authentication
import Servant.Server.Internal import Servant.Server.Internal
import Servant.Server.Internal.Authentication (strictProtect, AuthHandlers(AuthHandlers)) import Servant.Server.Internal.Authentication (strictProtect, AuthHandlers(AuthHandlers))
-- | An example of a custom authentication framework that checks a Cookie for a
-- value.
-- | Data we will use to test for authentication -- | Data we will use to test for authentication
data CookieAuth = CookieAuth { cookie :: ByteString } data CookieAuth = CookieAuth { cookie :: ByteString }

View file

@ -60,13 +60,13 @@ data instance AuthProtected authData usr subserver 'Lax =
, subServerLax :: subserver , subServerLax :: subserver
} }
-- | handy function to build an auth-protected bit of API with a Lax policy -- | handy function to build an auth-protected bit of API with a 'Lax' policy
laxProtect :: (authData -> IO (Maybe usr)) -- ^ check auth laxProtect :: (authData -> IO (Maybe usr)) -- ^ check auth
-> subserver -- ^ the handlers for the auth-aware bits of the API -> subserver -- ^ the handlers for the auth-aware bits of the API
-> AuthProtected authData usr subserver 'Lax -> AuthProtected authData usr subserver 'Lax
laxProtect = AuthProtectedLax laxProtect = AuthProtectedLax
-- | handy function to build an auth-protected bit of API with a Strict policy -- | handy function to build an auth-protected bit of API with a 'Strict' policy
strictProtect :: (authData -> IO (Maybe usr)) -- ^ check auth strictProtect :: (authData -> IO (Maybe usr)) -- ^ check auth
-> AuthHandlers authData -- ^ functions to call on auth failure -> AuthHandlers authData -- ^ functions to call on auth failure
-> subserver -- ^ handlers for the auth-protected bits of the API -> subserver -- ^ handlers for the auth-protected bits of the API