Compare commits

..

No commits in common. "41278e81a9f6aaa750662cde91ebe0127722c6ef" and "233a559aafe0561ced97f963922e97cc2f435f9c" have entirely different histories.

3 changed files with 51 additions and 37 deletions

View File

@ -22,33 +22,25 @@ License along with this program. If not, see
-}
{-# LANGUAGE OverloadedStrings #-}
module Password.App.Draw (drawFunc) where
import Brick (Widget, emptyWidget, txt, vBox)
import Brick.Forms (Form, formState, renderForm)
import Data.Text (Text)
import Brick (Widget, txt, vBox)
import Brick.Forms (renderForm)
import Lens.Micro ((^.))
import Password.App.Types
-- | Renders the application view
drawFunc :: AppState -> [Widget ResName]
drawFunc s = maybe [emptyWidget] drawPassForm $ s^.passForm
drawFunc s = case s^.appMode of
InitMode is -> drawPassForm is
drawPassForm :: Form (Text, Text) () ResName -> [Widget ResName]
drawPassForm f =
drawPassForm :: InitState -> [Widget ResName]
drawPassForm is =
[ vBox
[ renderForm f
, txt $ pfText $ formState f
[ renderForm $ is^.setPassForm
, txt $ is^.spfError
]
]
pfText :: (Text, Text) -> Text
pfText (pass, conf)
| pass == "" = "Password cannot be blank."
| pass /= conf = "Passwords do not match."
| otherwise = ""
--jl

View File

@ -43,7 +43,7 @@ import Control.Monad.IO.Class (liftIO)
import Control.Monad.State.Class (gets, put)
import Data.Aeson (decodeFileStrict)
import Graphics.Vty.Input.Events (Event (EvKey))
import Lens.Micro (each, (^.))
import Lens.Micro ((^.))
import Lens.Micro.Mtl (zoom)
import System.EasyFile
( createDirectoryIfMissing
@ -77,9 +77,9 @@ loadDatabase = zoom database $ liftIO
) >>= mapM_ put
fallbackHandler :: BrickEvent ResName () -> EventM ResName AppState ()
fallbackHandler e = gets (^.passForm) >>= \case
Just _ -> zoom (passForm.each) $ handleFormEvent e
Nothing -> return ()
fallbackHandler e = gets (^.appMode) >>= \case
InitMode _ -> zoom (appMode.initState.setPassForm) $
handleFormEvent e
getKeyDispatcher
:: AppState

View File

@ -27,13 +27,19 @@ License along with this program. If not, see
module Password.App.Types (
-- * Types
AppState (..),
AppMode (..),
InitState (..),
ResName (..),
-- * Lenses
-- ** AppState
randGen,
database,
mainPass,
passForm,
appMode,
-- ** AppMode
initState,
-- ** InitState
setPassForm,
spfError,
-- * Constructors
mkInitialState,
) where
@ -54,13 +60,23 @@ data AppState = AppState
-- ^ The random number generator
, _database :: PWDatabase
-- ^ The password database
, _mainPass :: String
-- ^ The main password
, _passForm :: Maybe PassForm
, _appMode :: AppMode
-- ^ The current operating mode
}
-- | A password form (with confirmation)
type PassForm = Form (Text, Text) () ResName
-- | The applicaiton's mode
newtype AppMode = InitMode
{ _initState :: InitState
-- ^ Initialization state
}
-- | Application initialization state
data InitState = InitState
{ _setPassForm :: Form (Text, Text) () ResName
-- ^ password form
, _spfError :: Text
-- ^ error message
}
-- | Resource identifier
data ResName
@ -68,22 +84,28 @@ data ResName
| ConfField
deriving (Eq, Ord, Show)
makeLenses ''AppState
concat <$> mapM makeLenses
[ ''AppState
, ''AppMode
, ''InitState
]
-- | Builds an initial state
mkInitialState :: MonadIO m => m AppState
mkInitialState = AppState
<$> initStdGen
<*> return newPWDatabase
<*> return ""
<*> return (Just newPassForm)
<*> return (InitMode newInitState)
-- | Constructs a blank password form
newPassForm :: PassForm
newPassForm = newForm
[ (txt "Master password: " <+>) @@= editPasswordField _1 PassField
, (txt "Confirm password: " <+>) @@= editPasswordField _2 ConfField
]
("", "")
-- | New `InitState` value
newInitState :: InitState
newInitState = InitState
( newForm
[ (txt "Master password: " <+>) @@= editPasswordField _1 PassField
, (txt "Confirm password: " <+>) @@= editPasswordField _2 ConfField
]
("", "")
)
""
--jl