defined data structure for master password form

This commit is contained in:
Jonathan Lamothe 2024-09-07 16:57:20 -04:00
parent a3f405d9c5
commit 2b427789d2
2 changed files with 65 additions and 10 deletions

View File

@ -39,7 +39,7 @@ import Brick
import Password.App.Types
-- | The main application
passmanApp :: App AppState () ()
passmanApp :: App AppState () ResName
passmanApp = App
{ appDraw = drawFunc
, appChooseCursor = neverShowCursor
@ -48,10 +48,10 @@ passmanApp = App
, appAttrMap = const $ attrMap (style 0) []
}
drawFunc :: AppState -> [Widget ()]
drawFunc :: AppState -> [Widget ResName]
drawFunc = const [emptyWidget]
eventHandler :: BrickEvent () () -> EventM () AppState ()
eventHandler :: BrickEvent ResName () -> EventM ResName AppState ()
eventHandler = const halt
--jl

View File

@ -22,28 +22,83 @@ License along with this program. If not, see
-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE OverloadedStrings, TemplateHaskell #-}
module Password.App.Types (
-- * Types
AppState (..),
AppMode (..),
InitState (..),
ResName (..),
-- * Lenses
-- ** AppState
randGen,
mkInitialState
appMode,
-- ** AppMode
initState,
-- ** InitState
setPassForm,
spfError,
-- * Constructors
mkInitialState,
) where
import Brick (txt, (<+>))
import Brick.Forms (Form, editPasswordField, newForm, (@@=))
import Control.Monad.IO.Class (MonadIO)
import Lens.Micro.TH
import Data.Text (Text)
import Lens.Micro (_1, _2)
import Lens.Micro.TH (makeLenses)
import System.Random (StdGen, initStdGen)
-- | The application state
newtype AppState = AppState
data AppState = AppState
{ _randGen :: StdGen
-- ^ The random number generator
} deriving (Eq, Show)
, _appMode :: AppMode
}
makeLenses ''AppState
-- | 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
= PassField
| ConfField
deriving (Eq, Ord, Show)
concat <$> mapM makeLenses
[ ''AppState
, ''AppMode
, ''InitState
]
-- | Builds an initial state
mkInitialState :: MonadIO m => m AppState
mkInitialState = AppState <$> initStdGen
mkInitialState = AppState
<$> initStdGen
<*> return (InitMode newInitState)
-- | New `InitState` value
newInitState :: InitState
newInitState = InitState
( newForm
[ (txt "Master password: " <+>) @@= editPasswordField _1 PassField
, (txt "Confirm password: " <+>) @@= editPasswordField _2 ConfField
]
("", "")
)
""
--jl