Compare commits

...

3 Commits

3 changed files with 37 additions and 51 deletions

View File

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

View File

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

View File

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