{-|

Module      : BlindPass
Description : The main module for the blindpass package
Copyright   : (C) 2020 Jonathan Lamothe
License     : GPL-3
Maintainer  : jonathan@jlamothe.net
Stability   : stable
Portability : POSIX

This program is free software: you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
the Free Software Foundation, either version 3 of the License, or (at
your option) any later version.

This program is distributed in the hope that it will be useful, but
WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the GNU
General Public License for more details.

You should have received a copy of the GNU General Public License
along with this program.  If not, see <https://www.gnu.org/licenses/>.

-}

module BlindPass (
  getPassword,
  checkPasswords,
  output,
) where

import System.IO (stderr, stdin, hFlush, hGetEcho, hPutStr, hSetEcho)

-- | Prompts the user for a password without echoing to the screen
getPassword
  :: String
  -- ^ The prompt to present to the user
  -> IO String
  -- ^ The user's response
getPassword :: String -> IO String
getPassword String
pStr = do
  Bool
echoMode <- Handle -> IO Bool
hGetEcho Handle
stdin
  Handle -> Bool -> IO ()
hSetEcho Handle
stdin Bool
False
  String -> IO ()
output String
pStr
  String
input <- IO String
getLine
  String -> IO ()
output String
"\n"
  Handle -> Bool -> IO ()
hSetEcho Handle
stdin Bool
echoMode
  String -> IO String
forall (m :: * -> *) a. Monad m => a -> m a
return String
input

-- | Checks the passwords entered by the user
checkPasswords
  :: String
  -- ^ The first password
  -> String
  -- ^ The second password
  -> IO a
  -- ^ Action to perform if the passwords don't match
  -> (String -> IO a)
  -- ^ Action to perform if the passwords match (takes the password as
  -- an input)
  -> IO a
checkPasswords :: String -> String -> IO a -> (String -> IO a) -> IO a
checkPasswords String
pass1 String
pass2 IO a
onFail String -> IO a
onPass
  | String
pass1 String -> String -> Bool
forall a. Eq a => a -> a -> Bool
== String
pass2 = String -> IO a
onPass String
pass1
  | Bool
otherwise      = IO a
onFail

-- | Outputs text to standard error
output
  :: String
  -- ^ The text to be output
  -> IO ()
output :: String -> IO ()
output String
str = do
  Handle -> String -> IO ()
hPutStr Handle
stderr String
str
  Handle -> IO ()
hFlush Handle
stderr

--jl