passman/app/Main.hs

106 lines
2.7 KiB
Haskell
Raw Normal View History

2018-12-06 22:03:38 -05:00
{-
passman
Copyright (C) 2018 Jonathan Lamothe
<jlamothe1980@gmail.com>
This program is free software: you can redistribute it and/or modify
it under the terms of the GNU Lesser 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
Lesser General Public License for more details.
2018-12-06 14:31:36 -05:00
2018-12-06 22:03:38 -05:00
You should have received a copy of the GNU Lesser General Public
License along with this program. If not, see
<https://www.gnu.org/licenses/>.
-}
2018-12-07 21:07:42 -05:00
{-# LANGUAGE TemplateHaskell #-}
2018-12-06 22:03:38 -05:00
module Main where
2018-12-06 14:31:36 -05:00
import Control.Lens (makeLenses, set, view)
import qualified Control.Monad.Trans.State as S
import Control.Monad (join)
import Control.Monad.Trans.Class (lift)
import Data.Maybe (fromJust)
import qualified System.Console.HCL as R
data Status = Status
{ _masterPass :: String
}
makeLenses ''Status
2018-12-07 21:07:42 -05:00
2018-12-06 14:31:36 -05:00
main :: IO ()
main = do
ms <- R.runRequest setup
case ms of
Nothing -> return ()
Just s -> S.evalStateT mainMenu s
2018-12-07 21:07:42 -05:00
setup :: R.Request Status
setup = fmap Status getMasterPass
getMasterPass :: R.Request String
2018-12-07 21:07:42 -05:00
getMasterPass = do
p1 <- R.required $ R.prompt "master password: " R.reqPassword
p2 <- R.required $ R.prompt "confirm master password: " R.reqPassword
2018-12-07 21:07:42 -05:00
if p1 /= p2
then do
R.reqIO $ putStrLn "passwords do not match"
R.reqFail
2018-12-07 21:07:42 -05:00
else return p1
2018-12-06 22:03:38 -05:00
mainMenu :: S.StateT Status IO ()
mainMenu = do
menu "Main Menu"
[ ( "change master password", changeMasterPass )
2018-12-09 14:31:58 -05:00
, ( "lock session", lockSession )
, ( "quit", quit )
]
changeMasterPass :: S.StateT Status IO ()
changeMasterPass = do
oldP <- S.gets $ view masterPass
newP <- req $ R.reqDefault getMasterPass oldP
S.modify $ set masterPass newP
mainMenu
2018-12-09 14:31:58 -05:00
lockSession :: S.StateT Status IO ()
lockSession = do
lift $ putStrLn "\nsession locked"
pass <- S.gets $ view masterPass
mx <- lift $ R.runRequest $ R.prompt "password: " $ R.reqPassword
case mx of
Nothing -> lockSession
Just x -> if x == pass
then mainMenu
else lockSession
quit :: S.StateT Status IO ()
quit = return ()
2018-12-09 11:23:50 -05:00
menu
:: String
-> [(String, S.StateT Status IO a)]
-> S.StateT Status IO a
menu title = reqState . R.prompt ("\n*** " ++ title ++ " ***") .
R.reqMenu . map menuItem
menuItem :: (String, a) -> (String, R.Request a)
menuItem (str, x) = (str, return x)
reqState :: R.Request (S.StateT s IO a) -> S.StateT s IO a
reqState = join . req
req :: R.Request a -> S.StateT s IO a
req = lift . fmap fromJust . R.runRequest . R.required
2018-12-06 22:03:38 -05:00
--jl