Hamming widget skeleton

This commit is contained in:
Jonathan Lamothe 2024-07-19 15:16:07 -04:00
parent 21242ecbfa
commit e216432a77
5 changed files with 102 additions and 4 deletions

View File

@ -24,6 +24,8 @@ library
Hamming Hamming
Hamming.App Hamming.App
Hamming.App.Types Hamming.App.Types
Hamming.App.Widgets
Hamming.App.Widgets.Internal
other-modules: other-modules:
Paths_hamming Paths_hamming
autogen-modules: autogen-modules:

View File

@ -34,7 +34,7 @@ import Brick.Widgets.Core (emptyWidget)
import Hamming.App.Types import Hamming.App.Types
mainApp :: App AppState () () mainApp :: App AppState () ResName
mainApp = App mainApp = App
{ appDraw = drawFunc { appDraw = drawFunc
, appChooseCursor = neverShowCursor , appChooseCursor = neverShowCursor
@ -43,10 +43,12 @@ mainApp = App
, appAttrMap = const $ forceAttrMap $ style 0 , appAttrMap = const $ forceAttrMap $ 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

View File

@ -27,9 +27,14 @@ License along with this program. If not, see
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
module Hamming.App.Types ( module Hamming.App.Types (
-- * Application State
AppState (..), AppState (..),
-- ** Lenses
hammingCode, hammingCode,
initialState -- * Resource Name
ResName,
-- * Constructors
initialState,
) where ) where
import Data.Word (Word16) import Data.Word (Word16)
@ -40,6 +45,8 @@ data AppState = AppState
{ _hammingCode :: Word16 { _hammingCode :: Word16
} }
type ResName = ()
makeLenses ''AppState makeLenses ''AppState
-- | Initial application state -- | Initial application state

View File

@ -0,0 +1,53 @@
{-|
Module : Hamming.App.Widgets
Description : Utilities for working with Hamming codes
Copyright : (C) Jonathan Lamothe
License : AGPL-3.0-or-later
Maintainer : jonathan@jlamothe.net
Stability : experimental
Portability : POSIX
This program is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as
published by the Free Software Foundation, either version 3 of the
License, or (at your option) any later version.
This program is distributed in the hope that it will be useful, but
WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public
License along with this program. If not, see
<https://www.gnu.org/licenses/>.
|-}
module Hamming.App.Widgets (hammingW) where
import Brick.AttrMap (attrName)
import Brick.Types (Widget)
import Brick.Widgets.Core (hBox, str, vBox, withAttr)
import Hamming.App.Types
import Hamming.App.Widgets.Internal
-- | generates a "Widget" from a hamming code
hammingW
:: AppState
-> Widget ResName
hammingW = withAttr (attrName "hamming")
. vBox
. map
( hBox
. map
( \(ns, v) -> foldr
(withAttr . attrName)
(str v)
ns
)
)
. hammingW'
--jl

View File

@ -0,0 +1,34 @@
{-|
Module : Hamming.App.Widgets.Internal
Description : Utilities for working with Hamming codes
Copyright : (C) Jonathan Lamothe
License : AGPL-3.0-or-later
Maintainer : jonathan@jlamothe.net
Stability : experimental
Portability : POSIX
This program is free software: you can redistribute it and/or modify
it under the terms of the GNU Affero General Public License as
published by the Free Software Foundation, either version 3 of the
License, or (at your option) any later version.
This program is distributed in the hope that it will be useful, but
WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the GNU
Affero General Public License for more details.
You should have received a copy of the GNU Affero General Public
License along with this program. If not, see
<https://www.gnu.org/licenses/>.
|-}
module Hamming.App.Widgets.Internal (hammingW') where
import Hamming.App.Types
hammingW' :: AppState -> [[([String], String)]]
hammingW' = undefined
--jl