Add support for authentication to servant-foreign and servant-js

This commit is contained in:
Arian van Putten 2015-10-03 00:11:11 +02:00
parent 011f094c4a
commit 81f48c6b14
3 changed files with 35 additions and 4 deletions

View file

@ -29,6 +29,7 @@ library
build-depends: base == 4.* build-depends: base == 4.*
, lens == 4.* , lens == 4.*
, servant == 0.5.* , servant == 0.5.*
, text >= 1.2 && < 1.3
hs-source-dirs: src hs-source-dirs: src
default-language: Haskell2010 default-language: Haskell2010
ghc-options: -Wall ghc-options: -Wall

View file

@ -54,10 +54,11 @@ import Control.Lens (makeLenses, (%~), (&), (.~),
import Data.Char (toLower, toUpper) import Data.Char (toLower, toUpper)
import Data.List import Data.List
import Data.Proxy import Data.Proxy
import Data.Text (Text)
import GHC.Exts (Constraint) import GHC.Exts (Constraint)
import GHC.TypeLits import GHC.TypeLits
import Servant.API import Servant.API
import Servant.API.Authentication
-- | Function name builder that simply concat each part together -- | Function name builder that simply concat each part together
concatCase :: FunctionName -> String concatCase :: FunctionName -> String
concatCase = concat concatCase = concat
@ -105,7 +106,11 @@ data HeaderArg = HeaderArg
| ReplaceHeaderArg | ReplaceHeaderArg
{ headerArgName :: String { headerArgName :: String
, headerPattern :: String , headerPattern :: String
} deriving (Eq, Show) }
| HeaderArgGen
{ headerArgName :: String
, headerArgGenBody :: (String -> String)
}
type MatrixArg = QueryArg type MatrixArg = QueryArg
@ -127,7 +132,7 @@ data Req = Req
, _reqHeaders :: [HeaderArg] , _reqHeaders :: [HeaderArg]
, _reqBody :: Bool , _reqBody :: Bool
, _funcName :: FunctionName , _funcName :: FunctionName
} deriving (Eq, Show) }
makeLenses ''QueryArg makeLenses ''QueryArg
makeLenses ''Segment makeLenses ''Segment
@ -201,6 +206,30 @@ instance (KnownSymbol sym, HasForeign sublayout)
where hname = symbolVal (Proxy :: Proxy sym) where hname = symbolVal (Proxy :: Proxy sym)
subP = Proxy :: Proxy sublayout subP = Proxy :: Proxy sublayout
instance (HasForeign sublayout)
=> HasForeign (AuthProtect (BasicAuth realm) (usr :: *) (policy :: AuthPolicy) :> sublayout) where
type Foreign (AuthProtect (BasicAuth realm) (usr :: *) (policy :: AuthPolicy) :> sublayout) = Foreign sublayout
foreignFor Proxy req =
foreignFor (Proxy :: Proxy sublayout) (req & reqHeaders <>~
[HeaderArgGen "Authorization" $ \authdata ->
"(function("++authdata++"){" ++
"return \"Basic \" + btoa("++authdata++".username+\":\"+"++authdata ++ ".password)" ++
"})("++authdata++")"
])
instance (HasForeign sublayout)
=> HasForeign (AuthProtect Text (usr :: *) (policy :: AuthPolicy) :> sublayout) where
type Foreign (AuthProtect Text (usr :: *) (policy :: AuthPolicy) :> sublayout) = Foreign sublayout
foreignFor Proxy req =
foreignFor (Proxy :: Proxy sublayout) (req & reqHeaders <>~
[HeaderArgGen "Authorization" $ \authdata ->
"(function("++authdata++"){" ++
"return \"Bearer \" + "++authdata++";"++
"})("++authdata++")"
])
instance Elem JSON list => HasForeign (Post list a) where instance Elem JSON list => HasForeign (Post list a) where
type Foreign (Post list a) = Req type Foreign (Post list a) = Req

View file

@ -111,6 +111,7 @@ toValidFunctionName [] = "_"
toJSHeader :: HeaderArg -> String toJSHeader :: HeaderArg -> String
toJSHeader (HeaderArg n) = toValidFunctionName ("header" <> n) toJSHeader (HeaderArg n) = toValidFunctionName ("header" <> n)
toJSHeader (HeaderArgGen n b) = b (toJSHeader (HeaderArg n))
toJSHeader (ReplaceHeaderArg n p) toJSHeader (ReplaceHeaderArg n p)
| pn `isPrefixOf` p = pv <> " + \"" <> rp <> "\"" | pn `isPrefixOf` p = pv <> " + \"" <> rp <> "\""
| pn `isSuffixOf` p = "\"" <> rp <> "\" + " <> pv | pn `isSuffixOf` p = "\"" <> rp <> "\" + " <> pv