haskell-servant / servant

Servat is a Haskell DSL for describing, serving, querying, mocking, documenting web applications and more!
https://docs.servant.dev/
1.81k stars 409 forks source link

Authentication #70

Closed aaronlevin closed 8 years ago

aaronlevin commented 9 years ago

Hi everyone!

I thought I'd open up an issue to act as a container for authentication-related discussion. The issue will be considered closed when the first iteration of authentication has been implemented, at which point further improvements will have their own issues.

Authentication

We want to support various types of authentication for http servers and clients:

Further, we want to account for the following (not a total list):

Out of scope for this iteration (but worth thinking about):

References:

I welcome any thoughts, ideas, or suggestions! I will be creating an auth branch to feature work and will let everyone know when that's done.

jkarni commented 9 years ago

Thanks a lot for opening the issue!

Another thing to think about is whether to have basic auth at all, or just go with digest auth. My inclination is to go with both, in case someone wants to provide authentication without the challenge + nonce dance, since we do provide HTTPS by default.

One design @aaronlevin and I discussed for Basic/Digest auth is as follows. A combinator, BasicAuth (realm :: Symbol) lookup, and a class

class BasicAuthLookup lkup a | lkup -> a where
   basicAuthLookup :: Proxy lkup -> String -> IO (Maybe a)

With

instance (HasServer a, BasicAuthLookup lkup val) => BasicAuth realm lookup :> a where
    type (Server (BasicAuth realm lookup :> a)) = val -> Server a
    route = ...

The idea being that users can easily provide access to whatever database or other method they use for authentication storage by declaring a new datatype with no constructor, and a corresponding instance for BasicAuthLookup. They can at their discretion choose what type their lookup will return for the rest of their handlers (most likely something like User) and we would be responsible for returning 403 in case of Nothing (or 401 as the case may be).

The design of Digest auth would be very similar. We would handle the nonce and MD5 details, so that I think for the user there would be no API difference.

All of that, however, is just a thought.

aaronlevin commented 9 years ago

@jkarni how do you feel about a new combinator for auth? Instead of :> using something like :-| or -| or to represent some kind of "block" and prevent people from putting auth midway through an endpoint definition.

i.e.:

type MyEndpoint = BasicAuth lkup User -| "hello" :> "world" :> GET '[JSON] World

jkarni commented 9 years ago

Why shouldn't they be allowed to put Auth midway through an endpoint? That breaks compositionality. E.g.

type MyApi1 = Auth ... :> "home" :> (ep1 :<|> ep2)
type MyApi2 = "home" :> (ep1 :<|> Auth ... :> ep2)

I want MyApi2 if I only want ep2 under authentication.

jkarni commented 9 years ago

Ah well, there's the problem of one endpoint having more than one auth/realm. We can write type families to check that's not the case and add constraints appropriately

aaronlevin commented 9 years ago

ok, I'll leave it as is and we'll deal with those scenarios when they come up. I didn't know the Alternative and Sub combinators worked so well together.

alpmestan commented 9 years ago

@aaronlevin It's also nice to be able to say "hey this auth business just works like any other combinator, it just does a lookup and let the request go through if the lookup succeeds". If we introduce more operators that may confuse people I think.

The design looks sound. So the idea would be to provide a class such as BasicAuthLookup for all the auth methods we want to cover (adapting to the specifics of each method of course) ?

aaronlevin commented 9 years ago

@alpmestan yeah, that's the plan. I'm currently implementing Basic auth as a prototype to help us solidify on the design. The idea @jkarni proposed is good, although I'm already running into some nastiness with GHC and type inference. Once we complete this I can then implement it for the other types of authenticating, specializing as needed.

alpmestan commented 9 years ago

Terrific! Let us know if we can help in any way. I have some ideas about these stuffs too but I'll wait and see what you come up with to see if I can stack them on top =)

aaronlevin commented 9 years ago

you can see where I am here on my fork. It's not compiling, with complains about ambiguity ;\ https://github.com/aaronlevin/servant/blob/auth/servant-server/src/Servant/Server/Internal.hs#L339

aaronlevin commented 9 years ago

(you can ignore all the error stuff, just placeholders for now)

aaronlevin commented 9 years ago

I'm off work now, but I'll try a simpler version tomorrow and see if I can build from there.

codedmart commented 9 years ago

@aaronlevin :+1:. I would love to help out anyway I can on this just let me know.

aaronlevin commented 9 years ago

@codemart thanks! I'm going to spend some time tomorrow and I'm still hitting inference walls I'll let you know!

jkarni commented 9 years ago

@aaronlevin the issue in your branch seems to be that you have BasicAuth realm authVal rather than BasicAuth realm lookup in the instance head.

aaronlevin commented 9 years ago

@jkarni yeah, i may have pushed after I was playing around with type inference. I can get it to compile if it looks like:

instance (HasServer sublayout, BasicAuthLookup lookup authVal) => HasServer (BasicAuth realm lookup authVal :> sublayout) where
    type ServerT (BasicAuth realm lookup authVal :> sublayout) m = authVal -> ServerT sublayout m

I need to put the authVal on BasicAuth, otherwise GHC will complain about a type variable appearing on the RHS with no bound on the LHS (in the context of HasServer's ServerT type declaration).

I feel like BasicAuth "some-realm" DB User is somewhat redundant when the BasicAuthLookup is parametrized against DB, but I'm not sure how to get around that. It does have the benefit of forcing the user to consider both the semantic "backend" (DB) and type returned (e.g. User) pairing for their authentication.

Thoughts?

jkarni commented 9 years ago

Aha. Well, then instead of having then fundep, I guess having an associated type synonym:

class BasicAuthLookup lookup
    type BasicAuthVal
    basicAuthLookup :: Proxy lkup -> String -> IO (Maybe (BasicAuthVal lookup))

Would allow you to do:

instance (HasServer sublayout, BasicAuthLookup lookup)
    => HasServer (BasicAuth realm lookup :> sublayout) where
    type ServerT (BasicAuth realm lookup  :> sublayout) m 
         = (BasicAuthVal lookup) -> ServerT sublayout m
aaronlevin commented 9 years ago

@jkarni ok, I'll try that.

aaronlevin commented 9 years ago

@jkarni worked! thanks.

aaronlevin commented 9 years ago

Alright, first pass for Basic Authentication:

I'll add better documentation and some tests once I get some feedback that this is the right approach. Specifically, am I handling the failure (401 and 403) idiomatically.

aaronlevin commented 9 years ago

oh, also, i can issue a PR if it's easier to code review.

aaronlevin commented 9 years ago

OK, so here is something interesting that has to do with the placement of BasicAuth. Consider the following two APIs:

type AuthAPI1 = "foo" :> BasicAuth "foo-realm" AuthDB :> Get '[JSON] Person
           :<|> "bar" :> BasicAuth "bar-realm" AuthDB :> Get '[JSON] Animal

type AuthAPI2 = BasicAuth "foo-realm" AuthDB :> "foo" :> Get '[JSON] Person
           :<|> "bar" :> BasicAuth "bar-realm" AuthDB :> Get '[JSON] Animal

What do you expect the following behaviour to be:

  1. For AuthAPI1: GET /bar will return ???
  2. For AuthAPI2: GET /bar will return ???

For AuthAPI1, the path will not match and the next route will be tried. The request will fail with the header WWW-Authenticate: realm="bar-realm" as predicted. :ok_hand:

For AuthAPI2, the authentication will be checked before the path, and since credentials are not provided, the request will fail with the header WWW-Authenticate: realm="foo-realm", which is not expected as the realm that protects /bar is bar-realm

So, I think what needs to happen is that we check that the route matches before attempting auth. I'll look into HasServer (a :<|> b) to see how this is done and then update and include a test-case.

fun!

aaronlevin commented 9 years ago

@jkarni after investigating the above for a little bit, I'm not sure the best way to go forward. I could add a datatype to RouteMismatch for Forbidden and NothAuthorized, but the downside to this is that several auth realms may be tried before finding the right match, possibly resulting in unexpected IO as different realms are tried.

We can't test subroutes because those they rely on data (like BasicAuthVal) for resolution. Ultimately, I just want to test "does the path match?" before considering the ServerT resolution. Is that possible?

jkarni commented 9 years ago

Ouch, my fault. It seems I got lucky with the example I gave in the talk, and didn't think long enough about it. Changing RouteMismatch will solve one problem - namely getting 403/401 when you should be getting other errors, or even a success - but it won't solve the problem of the wrong realm that you pointed out. In my mind, it seemed like a feature that the auth check would stop the routing from even trying to recurse deeper into the structure, but now I realize that doesn't make sense.

We have the same problem with returning Bad Request over Method Not Allowed simply because the former happens first in the type. There is, I think, no fundamental reason why this can't be fixed - we just need to thread more information through the routes. I had been putting all of that off with the intention of incorporating it along with the changes kosmikus outlined here, but given that the aforementioned problem is to my mind the biggest open issue with servant, and your auth changes also very important, it may be worth considering doing this change separately.

There is, I think, a solution involving a type family that "pushes down" the auth combinator to the leaves of the tree, but I need to think about the implications a bit more. Give me a day or two to mull this over? I'm sorry you ran into the dark corners of present-day servant, and into my own carelessness as well!

aaronlevin commented 9 years ago

Thanks for the response! Take your time. No need for apologies, I actually think this is pretty exciting :)

I'll try to think of some ideas inline with what you and kosnikus are thinking. I agree that it's best to wait for this outstanding issue to be resolved.

This is precisely why I wanted to start with Basic Authentication as I figured some nastiness would emerge!

👻 On Tue, May 12, 2015 at 5:20 PM Julian Arni notifications@github.com wrote:

Ouch, my fault. It seems I got lucky with the example I gave in the talk, and didn't think long enough about it. Changing RouteMismatch will solve one problem - namely getting 403/401 when you should be getting other errors, or even a success - but it won't solve the problem of the wrong realm that you pointed out. In my mind, it seemed like a feature that the auth check would stop the routing from even trying to recurse deeper into the structure, but now I realize that doesn't make sense.

We have the same problem with returning Bad Request over Method Not Allowed simply because the former happens first in the type. There is, I think, no fundamental reason why this can't be fixed - we just need to thread more information through the routes. I had been putting all of that off with the intention of incorporating it along with the changes kosmikus outlined here https://gist.github.com/kosmikus/79310bc1e40f6d651a0d, but given that the aforementioned problem is to my mind the biggest open issue with servant, and your auth changes also very important, it may be worth considering doing this change separately.

There is, I think, a solution involving a type family that "pushes down" the auth combinator to the leaves of the tree, but I need to think about the implications a bit more. Give me a day or two to mull this over? I'm sorry you ran into the dark corners of present-day servant, and into my own carelessness as well!

— Reply to this email directly or view it on GitHub https://github.com/haskell-servant/servant/issues/70#issuecomment-101425413 .

aaronlevin commented 9 years ago

@jkarni I think something along the lines of what kosmikus suggested will be helpful for this issue. It gives more semantic meaning to the combinators and will allow routes to gain subroute information in a meaningful way.

seanhess commented 9 years ago

Also keep in mind JSON Web Tokens, which are rad. I'm using them on my project. They can be used with Cookies or Headers.

jkarni commented 9 years ago

@aaronlevin The changes in #111 may suffice to make this possible now in a sensible way. On the other hand, we've also been discussing changing the RouteMismatch machinery, so it may make sense to wait a bit longer before updating your changes...

kosmikus commented 9 years ago

https://github.com/kosmikus/servant/tree/improved-routing-with-auth is my attempt to port the work by @aaronlevin to the improved-routing work. It compiles, but isn't in any way tested. But perhaps it's useful. If you have any questions, let me know.

aaronlevin commented 9 years ago

@jkarni @kosmikus hey! I just got back from Vacation two days ago. I'm in Berlin next week for a job interview, and then another job interview the following week. I'll try to find some time between then. If not, after that, I'm between jobs so will have plenty of time to help!

jhickner commented 9 years ago

This is great! I've been following along and attempting to adapt this for JSON web token authentication. I've run into an issue though. How do you handle validating the user's credentials when you can't hard-code the lookup into a class instance? The below works because the username and password are hard-coded, but what if you needed to access a db pool? How would you pass it in to basicAuthLookup?

data AuthDB
instance BasicAuthLookup AuthDB where
  type BasicAuthVal = Person
 basicAuthLookup _ user pass = if user == "servant" && pass == "server"
                               then return (Just alice)
                               else return Nothing
aaronlevin commented 9 years ago

I made a comment about this somewhere. The idea should be that you can perform an action in the ServantT monad which would mean you can do IO (or your own custom monad when that machinery is available) On Tue, Jun 23, 2015 at 3:12 AM Jason Hickner notifications@github.com wrote:

This is great! I've been following along and attempting to adapt this for JSON web token authentication. I've run into an issue though. How do you handle validating the user's credentials when you can't hard-code the lookup into a class instance? The below works because the username and password are hard-coded, but what if you needed to access a db pool? How would you pass it in to basicAuthLookup?

data AuthDB instance BasicAuthLookup AuthDB where type BasicAuthVal = Person basicAuthLookup _ user pass = if user == "servant" && pass == "server" then return (Just alice) else return Nothing

— Reply to this email directly or view it on GitHub https://github.com/haskell-servant/servant/issues/70#issuecomment-114387350 .

jhickner commented 9 years ago

OK, got it. So using your own monad with something like a ReaderT in it would be the only way to inject app-specific data into the combinator? Like your DB pool or your app's secret key?

alpmestan commented 9 years ago

We could even slightly change the class to make it look like:

class BasicAuthLookup lookup ctx where
    type BasicAuthVal
    basicAuthLookup :: Proxy lookup -> ctx -> B.ByteString -> B.ByteString -> IO (Maybe BasicAuthVal)

Where ctx could be a database connection, a simple Map, whatever you want. We might want to add a functional dependency | lookup -> ctx, or have the "context" be an associated type family. Would that be helpful/nicer?

jhickner commented 9 years ago

I like this! Nice and simple.

parsonsmatt commented 9 years ago

So, a lot of the current discussion seems to be centered around incorporating authorization along with authentication. I see these as separate problems, where authentication just gives you a Maybe User that the endpoint or possibly a further authorization combinator handles.

For instance, I might want to show different data based on whether or not a user is logged in, and other information about that user. But I also don't necessarily want to respond with Unauthorized.

type Api = "users" :> Authenticate :> Get '[JSON] [User]

indexUsers currentUser =
    case currentUser of
      Nothing -> return (minimalInfo allUsers)
      Just (user) -> case user of
                     User Admin -> return (allInfo allUsers)
                     User Basic -> return (someInfo allUsers)

Authenticate in this sense would provide some way of inspecting the request and returning Maybe User , but would defer authorization until later. An authorization combinator or the endpoint function itself could handle it.

I really like the way the Ruby library pundit works for authorization. You call authorize @resource, it inspects the resource and the current_user variable, and either raises an error or returns true. Defining authorizations is done like:

class Resource
  def show?
    user.admin? || resource.user_id == user.id
  end
end

I think something very close to this could be done in a type safe manner with type classes, but I haven't quite worked out how I want it all to look. Perhaps something like: https://gist.github.com/parsonsmatt/12cb2e444dd2024d9836

Anyway, just my thoughts :)

aaronlevin commented 9 years ago

@parsonsmatt this is a good point. You are correct that they are different, however, the general pattern of having a set of rules protecting a set of resources with error handling and possible side effects occur for both authentication and authorization. Therefore, once we figure out the general pattern for handling authentication (starting with Basic because it's the simplest), then we can start to think about roles and access and all the other fun stuff that happens with authorization (and how to combine the two).

I appreciate you supplying the pundit link. It's good to have a reference for other implementations. Thanks!

parsonsmatt commented 9 years ago

Yes! Absolutely. I agree. I think my primary difference in thought with current implementations is that the inspection of the request for an identity should be separated from actually responding to the request at that point, at least in the low level combinator. That should simplify the basic authentication story a bit. Instead of failing in the various non-successful case statements, it could do:

noAuth = route (Proxy :: Proxy sublayout) (action Nothing) request response

and this case statement case statement could be replaced with:

route (Proxy :: Proxy sublayout) (action maybeAuthData) request respond

deferring the handling of the missing user record until later.

aaronlevin commented 9 years ago

Update: I've rebased from HEAD and merged-in @kosmikus's changes. The BasicAuth stuff is compiling.

I had to do something weird with BasicAuthVal; I had to reference the lookup type otherwise GHC was complaining.

Some questions:

  1. are we happy with this design, especially with respect to how failure is handled?
  2. I will be adding the ctx as a param right away. Are we happy with @alpmestan's comment?
  3. I'm going to add some testing to ensure the subrouting works as we hope/thing it does.

code is here: https://github.com/aaronlevin/servant/tree/auth

jkarni commented 9 years ago

@aaronlevin on IRC you asked about whether we have a general method for threading configuration. The answer is that currently, no we don't. I think are a few options, though:

  1. Use ImplicitParams.
  2. Make a constructor for :>, analogously to :<|>.
  3. Change the type of serve, and the guts of HasServer, so that additional parameters can be passed at the top level.

I don't like 3, since it doesn't compose well. I think 1 might be fine, except that of course then users have to use implicit params, 2 is interesting. The idea is that if you have an endpoint like

     AuthProtected ... a :> Get '[JSON] Int

Your handler would look like:

  myA :> return 5

Or some such.

Thoughts?

alpmestan commented 9 years ago

I personally feel confident about none of the 3 propositions above. This might mean we have to stop and look around for alternative approaches. I for instance indeed didn't think my earlier suggestion through, as there's no way to pull a "context" out of thin air.

Let me try and sum up what we want/need.

Summary

Ideally we would just have to flip a switch somewhere to go from one to the other.

Idea

I've spent some time thinking about this today. Here's what I came up with. Any suggestions/feedback welcome. Feel free to take this code and distort in ways that you find interesting to make it more flexible or nicer to use etc.

-- * How this would be used

type MyUser = ByteString

type MyAPI = "public" :> Get '[JSON] PublicData
        :<|> AuthProtect (BasicAuth "Secret Haskell Center")
                         MyUser
                         Lax
          :> SecretAPI

type SecretAPI = Get '[JSON] String

secretServer :: Maybe MyUser -> Server SecretAPI
secretServer Nothing  = return "No user"
secretServer (Just u) = return (show u)

server :: Pool Connection -> Server MyAPI
server pool = publicDataStuff
         :<|> laxProtect (myCheck pool) secretServer

  where myCheck pool (BasicAuth usr pass) =
          -- or make use of the connection pool, as you wish =)
          if usr == "admin" && pass == "admin"
            then Just "admin"
            else Nothing

-- * How this could be implemented

-- An instance of AuthData is anything
-- that we can get from the request
-- (usually from headers or cookies though)
class AuthData a where
  authData :: Request -> Maybe a

-- data type to hold basic auth daa
data BasicAuth (realm :: Symbol) = BA
  { baUser  :: ByteString
  , baPass  :: ByteString
  } deriving (Eq, Show)

instance AuthData (BasicAuth realm) where
  authData req = -- margin too small, sorry
  -- see https://github.com/haskell-servant/servant/compare/master...aaronlevin:auth#diff-350ecd5a117c9bc3dd30e3b9feceb5ceR254

-- and DigestAuth, JWT, ...

-- maybe some of them would require that 'authData' has the following type:
-- > authData :: Request -> IO (Maybe a) ? this wouldn't be a problem,
-- that would work for us just as well, since it's meant to be run in
-- the HasServer instance and we're allowed to perform IO there

-- we can be either Strict or Lax.
-- Strict: all handlers under 'AuthProtect' take a 'usr' argument.
--         when auth fails, we call user-supplied handlers to respond.
-- Lax: all handlers under 'AuthProtect' take a 'Maybe usr' argument.
--      when auth fails, we call the handlers with 'Nothing'.
data AuthPolicy = Strict | Lax

-- the combinator to be used in API types
data AuthProtect authdata usr (policy :: AuthPolicy)

-- what we'll ask user to provide at the server-level when we see a 'AuthProtect'
-- combinator in an API type
data family AuthProtected authdata usr subserver :: AuthPolicy -> *

-- the concrete type to provide when "in Strict mode"
data instance AuthProtected authdata usr subserver 'Strict = APS
  { checkAuth :: authdata -> IO (Maybe usr)
  , subServer :: subserver
  , authHandlers :: AuthHandlers authdata
  }

data AuthHandlers authdata = AH
  { -- we couldn't find the right type of auth data (or any, for that matter)
    onMissingAuthData :: IO Response
  , -- we found the right type of auth data in the request but the check failed
    onUnauthorized    :: authdata -> IO Response
  }

-- and maybe other fields? but given the current code by Aaron & Andres,
-- it seems those are enough
-- also, we might want something else than Response, which we don't use elsewhere
-- in servant? Like ServantErr or something? Don't know, please let me know what
-- you think about that.

-- the concrete type to provide when "in Lax mode"
data instance AuthProtected authdata usr subserver 'Lax = APL
  { checkAuth :: authdata -> IO (Maybe usr)
  , subServer :: subserver
  }

-- handy function to build an auth-protected bit of API with a Lax policy
laxProtect :: (authdata -> IO (Maybe usr)) -- ^ check auth
           -> subserver                    -- ^ the handlers for the auth-aware bits of the API
           -> AuthProtected authdata usr subserver 'Lax
laxProtect = APL

-- handy function to build an auth-protected bit of API with a Strict policy
strictProtect :: (authdata -> IO (Maybe usr)) -- ^ check auth
              -> subserver                    -- ^ handlers for the auth-protected bits of the API
              -> AuthHandlers authdata        -- ^ functions to call on auth failure
strictProtect = APS

instance (AuthData authdata, HasServer sublayout)
      => HasServer (AuthProtect authdata usr Strict :> sublayout) where
  type ServerT (AuthProtect authdata usr Strict :> sublayout) m
    = AuthProtected authdata usr (usr -> ServerT sublayout m) Strict

  route _ (APS check action handlers) = WithRequest $ \req ->
    case authData req of
      -- couldn't find the right auth data
      Nothing -> do
        -- we're in Strict mode: we don't let
        -- the request go and instead call the provided
        -- "on missing auth data" handler
        resp <- onMissingAuthData handlers
        -- and then send the response

      -- we found the right type of auth data
      Just d -> do
        -- perform the user-supplied check
        musr <- check d
        case musr of
          -- didn't match any user, we call the
          -- user supplied unauthorized handler
          Nothing -> do
            resp <- onUnauthorized handlers d
            -- and then send the response

          -- matches an user. we let the request go and pass
          -- the user to the "subserver"
          Just usr -> action usr

instance (AuthData authdata, HasServer sublayout)
      => HasServer (AuthProtect authdata usr Lax :> sublayout) where
  type ServerT (AuthProtect authdata usr Lax :> sublayout) m
    = AuthProtected authdata usr (Maybe usr -> ServerT sublayout m) Lax

  route _ (APL check action) = WithRequest $ \req -> do
    -- we try to get the right auth data and perform a check on it
    -- but we don't care about which one fails. the "subserver"
    -- promises to handle a 'Maybe', so we just pass whatever result
    -- we get. Hence 'Lax'.
    musr <- maybe Nothing check (authData req)
    action musr
aaronlevin commented 9 years ago

@alpmestan I think this is good. I think we can build various authentication types out of this (as you allude above). I will go and implement what you've got here and see what snags I get into (if any).

In the interim we should be clear about one thing at this point: this does not handle the case of authorization (which is fine).

authorization: So, we've got our AuthProtected server and now our API writers have access to the usr data for their requests. Now, how do we determine if the usr is authorized for the request? Is this something we want as part of this current model, or do we want more combinators to handle this? (I err on the side of more combinators).

The test example: someone is requesting GET /user/1234. We have authenticated them, and generated the ApiUser type from the Request data. Now we need check if they are authorized to get the information for user 1234!

aaronlevin commented 9 years ago

Update: slowly chugging along. https://github.com/aaronlevin/servant/commit/cc01deaa878e05c93f8eec281b96d56e53b9cdd5

berdario commented 9 years ago

Sorry for the drive-by comment, I'm completely new to servant (in fact I just found this issue while googling for the servant tutorial)

but I'm a bit saddened that apparently this effort for implementing authentication in servant is (seems to be?) completely ignoring client side certificates, if the following is the complete list of methods in scope:

Client side certificates (if my understanding is correct) are the only solution that would prevent a MITM of the traffic going to client, even in the event of the server certificate's private key being leaked... Usually, the criticism of client certificates complains about the UI (which I frankly prefer to cookie based auth)... but for an HTTP api like one built with servant this concern should be moot

alpmestan commented 9 years ago

Hey @berdario,

Please do not apologize, we're happy to get as much input as people care to give on this topic.

Regarding the heart of your comment, the thing is, there will never be a complete list. This is all extensible, the list (Basic, Digest, Cookie, Token) is just what we'd like to offer out of the box in the next release, for the first release with some auth combinators.

People are free to write implementations for other types of auth, and offer to integrate that into the core servant packages. In fact, if you are willing to help @aaronlevin and/or myself and/or anyone else interested in this, we could very well try to think of a way to implement support for client side certificates.

However, it seems to me this one would be significantly different from the others. Do you have an idea of how this could look like, from an user's point of view (a servant user, that is)?

aaronlevin commented 9 years ago

@berdario thanks for your comments. We are developing a general framework for implementing various authentication techniques, which should allow others to implement a certificate-based technique (if it makes sense as per alp's comment above).

Transport-layer security (TLS / HTTPS) will be implemented by the sever (usually via warp-tls).

aaronlevin commented 9 years ago

I can't imagine a request-level, certificate-based authentication without including some kind of signature in the Request.

aaronlevin commented 9 years ago

Side note: one of the major reasons people don't use certificate-based authentication is because a lot of http clients run in a browser, which don't have a secure way of provisioning and storing certificates. Or at least this is what I understood from asking this very question to a chromium engineer.

jkarni commented 9 years ago

Client certs seem like a pretty legitimate request. With warp-tls and http-client-tls they shouldn't be hard. Not sure if the approach outlined here should be generalized to include client certs, or if there should be a separate issue altogether (from an implementation perspective, client certs are quite different).

berdario commented 9 years ago

@alpmestan yup, especially because it's a bit different from the others I thought that it would be best to design/think about it early

I'd be glad to help out... but I'm not a servant user yet, and I don't know if I'll have enough time to actually learn it well enough to contribute with code

@aaronlevin

What do you mean with

I can't imagine a request-level, certificate-based authentication without including some kind of signature in the Request.

? if you're talking about a signature for integrity purposes, shouldn't that be handled by TLS itself? I guess I completely missed the point

I obviously know a lot less about this than any chromium engineer: my experience with client certificates is limited to the ones I used to authenticate as a cacert.org user but storing certificates should not be any different than passwords... and browsers already have access to OS's keychains (in some cases... or have an encrypted store of their own) and provisioning... well, if there's already a TLS connection estabilished (at account-creation time, or to use client certificates to supplement normal cookie-based auth with a more secure alternative) the channel should be already pretty secure

Or is the problem with browsers and client side certficates related to handling authentication in Javascript?

aaronlevin commented 9 years ago

@berdario I just mean that most combinators in servant-server deal with Request-level information. This isn't to say that cert-based authentication can't be done, just that it would be a departure from the way many combinators are currently written.

For example, how do we pass information from the client's certificate to warp (likely via warp-tls) and how is it then threaded to various servant-combinators? We would need to figure this out, as the cert is used in the handshake and cert information isn't necessarily passed with the HTTP request (I could be wrong here, feel free to clarify!).

I don't have much experience with cert-based authentication. I'm happy to take the javascript conversation offline, as it's kind of interesting and I can go into more detail with what I was told!

To make this a lttle easier, could you outline a point-form flow of how this might work?