{-# Language OverloadedStrings #-}
{-|
Module      : Client.Authentication.Ecdsa
Description : Binding to ecdsatool
Copyright   : (c) Eric Mertens, 2016
License     : ISC
Maintainer  : emertens@gmail.com

Implementation of ECDSA-NIST256P-CHALLENGE SASL authentication mode
as implemented at <https://github.com/kaniini/ecdsatool>.

Using this mode requires that the @ecdsa@ utility program is available
in your search path.

-}
module Client.Authentication.Ecdsa
  ( authenticationMode
  , encodeAuthentication
  , computeResponse
  ) where

import           Control.Exception (displayException, try)
import           Data.Text (Text)
import qualified Data.Text as Text
import qualified Data.Text.Encoding as Text
import           System.Process (readProcess)
import           Irc.Commands (AuthenticatePayload(..))


-- | Identifier for SASL ECDSA challenge response authentication
-- using curve NIST256P.
--
-- @ECDSA-NIST256P-CHALLENGE@
authenticationMode :: Text
authenticationMode :: Text
authenticationMode = Text
"ECDSA-NIST256P-CHALLENGE"


-- | Encode a username as specified in this authentication mode.
encodeAuthentication ::
  Maybe Text {- ^ authorization identity  -} ->
  Text {- ^ authentication identity -} ->
  AuthenticatePayload
encodeAuthentication :: Maybe Text -> Text -> AuthenticatePayload
encodeAuthentication Maybe Text
Nothing Text
authc =
  ByteString -> AuthenticatePayload
AuthenticatePayload (Text -> ByteString
Text.encodeUtf8 Text
authc)
encodeAuthentication (Just Text
authz) Text
authc =
  ByteString -> AuthenticatePayload
AuthenticatePayload (Text -> ByteString
Text.encodeUtf8 (Text
authc Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
"\0" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<> Text
authz))


-- | Compute the response for a given challenge using the @ecdsatool@
-- executable which must be available in @PATH@.
computeResponse ::
  FilePath                {- ^ private key file                 -} ->
  Text                    {- ^ challenge string                 -} ->
  IO (Either String Text) {- ^ error message or response string -}
computeResponse :: FilePath -> Text -> IO (Either FilePath Text)
computeResponse FilePath
privateKeyFile Text
challenge =
  do Either IOException FilePath
res <- IO FilePath -> IO (Either IOException FilePath)
forall e a. Exception e => IO a -> IO (Either e a)
try (IO FilePath -> IO (Either IOException FilePath))
-> IO FilePath -> IO (Either IOException FilePath)
forall a b. (a -> b) -> a -> b
$ FilePath -> [FilePath] -> FilePath -> IO FilePath
readProcess
                    FilePath
"ecdsatool"
                    [FilePath
"sign", FilePath
privateKeyFile, Text -> FilePath
Text.unpack Text
challenge]
                    FilePath
"" -- stdin
     Either FilePath Text -> IO (Either FilePath Text)
forall (m :: * -> *) a. Monad m => a -> m a
return (Either FilePath Text -> IO (Either FilePath Text))
-> Either FilePath Text -> IO (Either FilePath Text)
forall a b. (a -> b) -> a -> b
$! case FilePath -> [FilePath]
words (FilePath -> [FilePath])
-> Either IOException FilePath -> Either IOException [FilePath]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Either IOException FilePath
res of
                 Right [FilePath
resp] -> Text -> Either FilePath Text
forall a b. b -> Either a b
Right (Text -> Either FilePath Text) -> Text -> Either FilePath Text
forall a b. (a -> b) -> a -> b
$! FilePath -> Text
Text.pack FilePath
resp
                 Right [FilePath]
_      -> FilePath -> Either FilePath Text
forall a b. a -> Either a b
Left FilePath
"bad sasl ecdsa response message"
                 Left IOException
e       -> FilePath -> Either FilePath Text
forall a b. a -> Either a b
Left (IOException -> FilePath
forall e. Exception e => e -> FilePath
displayException (IOException
e :: IOError))