Commit 44d898e8 authored by Przemyslaw Kaminski's avatar Przemyslaw Kaminski

[API] disable xsrf for cookie GET requests

Also, list API works now.  Only the file isn't downloaded yet.
parent 03d73fca
......@@ -208,7 +208,7 @@ type GargAPI' =
-- auth and capabilities.
:<|> GargPrivateAPI
type GargPrivateAPI = SA.Auth '[SA.JWT] AuthenticatedUser :> GargPrivateAPI'
type GargPrivateAPI = SA.Auth '[SA.JWT, SA.Cookie] AuthenticatedUser :> GargPrivateAPI'
type GargAdminAPI
-- Roots endpoint
......
......@@ -24,11 +24,8 @@ module Gargantext.API.Ngrams.List
where
import Data.Aeson
-- import qualified Data.ByteString.Lazy as BSL
import Data.List (zip)
import Data.Map (Map, toList, fromList)
-- import qualified Data.Text as T
-- import qualified Data.Text.Encoding as TE
import Network.HTTP.Media ((//), (/:))
import Servant
......@@ -52,7 +49,7 @@ type API = Get '[JSON] NgramsList
:<|> Get '[HTML] NgramsList
api :: ListId -> GargServer API
api l = get l :<|> put l :<|> get l
api l = get l :<|> put l :<|> getHtml l
get :: RepoCmdM env err m
=> ListId -> m NgramsList
......@@ -65,7 +62,6 @@ getHtml :: RepoCmdM env err m
getHtml lId = do
lst <- get lId
return lst
--return $ TE.decodeUtf8 $ BSL.toStrict $ encode lst
-- TODO : purge list
......
......@@ -48,7 +48,7 @@ import Data.ByteString (ByteString)
import qualified Data.ByteString.Lazy as L
import Servant
import Servant.Auth.Server (defaultJWTSettings, JWTSettings, CookieSettings, defaultCookieSettings, readKey, writeKey)
import Servant.Auth.Server (defaultJWTSettings, JWTSettings, CookieSettings(..), XsrfCookieSettings(..), defaultCookieSettings, defaultXsrfCookieSettings, readKey, writeKey)
import Servant.Client (BaseUrl, parseBaseUrl)
import qualified Servant.Job.Core
import Servant.Job.Async (newJobEnv, defaultSettings, HasJobEnv(..), Job)
......@@ -106,9 +106,11 @@ devSettings jwkFile = do
, _sendLoginEmails = LogEmailToConsole
, _scrapydUrl = fromMaybe (panic "Invalid scrapy URL") $ parseBaseUrl "http://localhost:6800"
, _fileFolder = "data"
, _cookieSettings = defaultCookieSettings -- TODO-SECURITY tune
, _cookieSettings = defaultCookieSettings { cookieXsrfSetting = Just xsrfCookieSetting } -- TODO-SECURITY tune
, _jwtSettings = defaultJWTSettings jwk -- TODO-SECURITY tune
}
where
xsrfCookieSetting = defaultXsrfCookieSettings { xsrfExcludeGet = True }
......
Markdown is supported
0% or
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment