{-# Language OverloadedStrings #-}
module Client.Authentication.Ecdsa
( authenticationMode
, encodeAuthentication
, computeResponse
) where
import Control.Exception (displayException, try)
import Data.ByteString.Lazy qualified as L
import Data.Text (Text)
import Data.Text qualified as Text
import Data.Text.Encoding qualified as Text
import Irc.Commands (AuthenticatePayload(..))
import System.Process.Typed (readProcessStdout_, proc)
authenticationMode :: Text
authenticationMode :: Text
authenticationMode = Text
"ECDSA-NIST256P-CHALLENGE"
encodeAuthentication ::
Maybe Text ->
Text ->
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))
computeResponse ::
FilePath ->
Text ->
IO (Either String Text)
computeResponse :: String -> Text -> IO (Either String Text)
computeResponse String
privateKeyFile Text
challenge =
do Either IOError ByteString
res <- IO ByteString -> IO (Either IOError ByteString)
forall e a. Exception e => IO a -> IO (Either e a)
try (ProcessConfig () () () -> IO ByteString
forall (m :: * -> *) stdin stdoutIgnored stderr.
MonadIO m =>
ProcessConfig stdin stdoutIgnored stderr -> m ByteString
readProcessStdout_ (String -> [String] -> ProcessConfig () () ()
proc String
"ecdsatool" [String
"sign", String
privateKeyFile, Text -> String
Text.unpack Text
challenge]))
Either String Text -> IO (Either String Text)
forall a. a -> IO a
forall (m :: * -> *) a. Monad m => a -> m a
return (Either String Text -> IO (Either String Text))
-> Either String Text -> IO (Either String Text)
forall a b. (a -> b) -> a -> b
$! case Either IOError ByteString
res of
Left IOError
e -> String -> Either String Text
forall a b. a -> Either a b
Left (IOError -> String
forall e. Exception e => e -> String
displayException (IOError
e :: IOError))
Right ByteString
resp ->
case Text -> [Text]
Text.words (Text -> [Text])
-> Either UnicodeException Text -> Either UnicodeException [Text]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> ByteString -> Either UnicodeException Text
Text.decodeUtf8' (ByteString -> ByteString
L.toStrict ByteString
resp) of
Left UnicodeException
e -> String -> Either String Text
forall a b. a -> Either a b
Left (UnicodeException -> String
forall e. Exception e => e -> String
displayException UnicodeException
e)
Right [Text
str] -> Text -> Either String Text
forall a b. b -> Either a b
Right Text
str
Right [Text]
_ -> String -> Either String Text
forall a b. a -> Either a b
Left String
"bad sasl ecdsa response message"