defined data structure for master password form
This commit is contained in:
parent
a3f405d9c5
commit
2b427789d2
|
@ -39,7 +39,7 @@ import Brick
|
||||||
import Password.App.Types
|
import Password.App.Types
|
||||||
|
|
||||||
-- | The main application
|
-- | The main application
|
||||||
passmanApp :: App AppState () ()
|
passmanApp :: App AppState () ResName
|
||||||
passmanApp = App
|
passmanApp = App
|
||||||
{ appDraw = drawFunc
|
{ appDraw = drawFunc
|
||||||
, appChooseCursor = neverShowCursor
|
, appChooseCursor = neverShowCursor
|
||||||
|
@ -48,10 +48,10 @@ passmanApp = App
|
||||||
, appAttrMap = const $ attrMap (style 0) []
|
, appAttrMap = const $ attrMap (style 0) []
|
||||||
}
|
}
|
||||||
|
|
||||||
drawFunc :: AppState -> [Widget ()]
|
drawFunc :: AppState -> [Widget ResName]
|
||||||
drawFunc = const [emptyWidget]
|
drawFunc = const [emptyWidget]
|
||||||
|
|
||||||
eventHandler :: BrickEvent () () -> EventM () AppState ()
|
eventHandler :: BrickEvent ResName () -> EventM ResName AppState ()
|
||||||
eventHandler = const halt
|
eventHandler = const halt
|
||||||
|
|
||||||
--jl
|
--jl
|
||||||
|
|
|
@ -22,28 +22,83 @@ License along with this program. If not, see
|
||||||
|
|
||||||
-}
|
-}
|
||||||
|
|
||||||
{-# LANGUAGE TemplateHaskell #-}
|
{-# LANGUAGE OverloadedStrings, TemplateHaskell #-}
|
||||||
|
|
||||||
module Password.App.Types (
|
module Password.App.Types (
|
||||||
|
-- * Types
|
||||||
AppState (..),
|
AppState (..),
|
||||||
|
AppMode (..),
|
||||||
|
InitState (..),
|
||||||
|
ResName (..),
|
||||||
|
-- * Lenses
|
||||||
|
-- ** AppState
|
||||||
randGen,
|
randGen,
|
||||||
mkInitialState
|
appMode,
|
||||||
|
-- ** AppMode
|
||||||
|
initState,
|
||||||
|
-- ** InitState
|
||||||
|
setPassForm,
|
||||||
|
spfError,
|
||||||
|
-- * Constructors
|
||||||
|
mkInitialState,
|
||||||
) where
|
) where
|
||||||
|
|
||||||
|
import Brick (txt, (<+>))
|
||||||
|
import Brick.Forms (Form, editPasswordField, newForm, (@@=))
|
||||||
import Control.Monad.IO.Class (MonadIO)
|
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)
|
import System.Random (StdGen, initStdGen)
|
||||||
|
|
||||||
-- | The application state
|
-- | The application state
|
||||||
newtype AppState = AppState
|
data AppState = AppState
|
||||||
{ _randGen :: StdGen
|
{ _randGen :: StdGen
|
||||||
-- ^ The random number generator
|
-- ^ 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
|
-- | Builds an initial state
|
||||||
mkInitialState :: MonadIO m => m AppState
|
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
|
--jl
|
||||||
|
|
Loading…
Reference in New Issue
Block a user