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 module Password.App.Draw (drawFunc) where
import Brick (Widget, emptyWidget, txt, vBox) import Brick (Widget, txt, vBox)
import Brick.Forms (Form, formState, renderForm) import Brick.Forms (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 = maybe [emptyWidget] drawPassForm $ s^.passForm drawFunc s = case s^.appMode of
InitMode is -> drawPassForm is
drawPassForm :: Form (Text, Text) () ResName -> [Widget ResName] drawPassForm :: InitState -> [Widget ResName]
drawPassForm f = drawPassForm is =
[ vBox [ vBox
[ renderForm f [ renderForm $ is^.setPassForm
, txt $ pfText $ formState f , txt $ is^.spfError
] ]
] ]
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 (each, (^.)) import Lens.Micro ((^.))
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 (^.passForm) >>= \case fallbackHandler e = gets (^.appMode) >>= \case
Just _ -> zoom (passForm.each) $ handleFormEvent e InitMode _ -> zoom (appMode.initState.setPassForm) $
Nothing -> return () handleFormEvent e
getKeyDispatcher getKeyDispatcher
:: AppState :: AppState

View File

@ -27,13 +27,19 @@ 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,
mainPass, appMode,
passForm, -- ** AppMode
initState,
-- ** InitState
setPassForm,
spfError,
-- * Constructors -- * Constructors
mkInitialState, mkInitialState,
) where ) where
@ -54,13 +60,23 @@ data AppState = AppState
-- ^ The random number generator -- ^ The random number generator
, _database :: PWDatabase , _database :: PWDatabase
-- ^ The password database -- ^ The password database
, _mainPass :: String , _appMode :: AppMode
-- ^ The main password -- ^ The current operating mode
, _passForm :: Maybe PassForm
} }
-- | A password form (with confirmation) -- | The applicaiton's mode
type PassForm = Form (Text, Text) () ResName 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 -- | Resource identifier
data ResName data ResName
@ -68,22 +84,28 @@ data ResName
| ConfField | ConfField
deriving (Eq, Ord, Show) deriving (Eq, Ord, Show)
makeLenses ''AppState concat <$> mapM makeLenses
[ ''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 "" <*> return (InitMode newInitState)
<*> return (Just newPassForm)
-- | Constructs a blank password form -- | New `InitState` value
newPassForm :: PassForm newInitState :: InitState
newPassForm = newForm newInitState = InitState
[ (txt "Master password: " <+>) @@= editPasswordField _1 PassField ( newForm
, (txt "Confirm password: " <+>) @@= editPasswordField _2 ConfField [ (txt "Master password: " <+>) @@= editPasswordField _1 PassField
] , (txt "Confirm password: " <+>) @@= editPasswordField _2 ConfField
("", "") ]
("", "")
)
""
--jl --jl