Add BasicAuth data type

This commit is contained in:
aaron levin 2015-05-11 16:16:34 -04:00 committed by Arian van Putten
parent 52b58d0fe9
commit 20599d7bba
3 changed files with 29 additions and 0 deletions

View file

@ -26,6 +26,7 @@ library
exposed-modules:
Servant.API
Servant.API.Alternative
Servant.API.Authentication
Servant.API.Capture
Servant.API.ContentTypes
Servant.API.Delete

View file

@ -5,6 +5,8 @@ module Servant.API (
-- | Type-level combinator for expressing subrouting: @':>'@
module Servant.API.Alternative,
-- | Type-level combinator for alternative endpoints: @':<|>'@
module Servant.API.Authentication,
-- | Type-level combinator for endpoints requiring auth: @'BasicAuth'@
-- * Accessing information from the request
module Servant.API.Capture,
@ -60,6 +62,7 @@ module Servant.API (
) where
import Servant.API.Alternative ((:<|>) (..))
import Servant.API.Authentication (BasicAuth)
import Servant.API.Capture (Capture)
import Servant.API.ContentTypes (Accept (..), FormUrlEncoded,
FromFormUrlEncoded (..), JSON,

View file

@ -0,0 +1,25 @@
{-# LANGUAGE DataKinds #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE PolyKinds #-}
{-# OPTIONS_HADDOCK not-home #-}
module Servant.API.Authentication (BasicAuth) where
import Data.Typeable (Typeable)
import GHC.TypeLits (Symbol)
-- | Basic Authentication with respect to a specified @realm@ and a @lookup@
-- type to encapsulate authentication logic.
--
-- Example:
-- >>> type AuthLookup = Text -> IO User
-- >>> type MyApi = BasicAuth "book-realm" :> "books" :> Get '[JSON] [Book]
data BasicAuth (realm :: Symbol) lookup
deriving (Typeable)
-- $setup
-- >>> import Servant.API
-- >>> import Data.Aeson
-- >>> import Data.Text
-- >>> data User
-- >>> data Book
-- >>> instance ToJSON Book where { toJSON = undefined }