diff --git a/hamming.cabal b/hamming.cabal
index eb431a0..40d4dd4 100644
--- a/hamming.cabal
+++ b/hamming.cabal
@@ -24,6 +24,8 @@ library
Hamming
Hamming.App
Hamming.App.Types
+ Hamming.App.Widgets
+ Hamming.App.Widgets.Internal
other-modules:
Paths_hamming
autogen-modules:
diff --git a/src/Hamming/App.hs b/src/Hamming/App.hs
index 79b165e..02328e0 100644
--- a/src/Hamming/App.hs
+++ b/src/Hamming/App.hs
@@ -34,7 +34,7 @@ import Brick.Widgets.Core (emptyWidget)
import Hamming.App.Types
-mainApp :: App AppState () ()
+mainApp :: App AppState () ResName
mainApp = App
{ appDraw = drawFunc
, appChooseCursor = neverShowCursor
@@ -43,10 +43,12 @@ mainApp = App
, appAttrMap = const $ forceAttrMap $ 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
diff --git a/src/Hamming/App/Types.hs b/src/Hamming/App/Types.hs
index bdd725e..d34ded7 100644
--- a/src/Hamming/App/Types.hs
+++ b/src/Hamming/App/Types.hs
@@ -27,9 +27,14 @@ License along with this program. If not, see
{-# LANGUAGE TemplateHaskell #-}
module Hamming.App.Types (
+ -- * Application State
AppState (..),
+ -- ** Lenses
hammingCode,
- initialState
+ -- * Resource Name
+ ResName,
+ -- * Constructors
+ initialState,
) where
import Data.Word (Word16)
@@ -40,6 +45,8 @@ data AppState = AppState
{ _hammingCode :: Word16
}
+type ResName = ()
+
makeLenses ''AppState
-- | Initial application state
diff --git a/src/Hamming/App/Widgets.hs b/src/Hamming/App/Widgets.hs
new file mode 100644
index 0000000..985489f
--- /dev/null
+++ b/src/Hamming/App/Widgets.hs
@@ -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
+.
+
+|-}
+
+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
diff --git a/src/Hamming/App/Widgets/Internal.hs b/src/Hamming/App/Widgets/Internal.hs
new file mode 100644
index 0000000..d05fe02
--- /dev/null
+++ b/src/Hamming/App/Widgets/Internal.hs
@@ -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
+.
+
+|-}
+
+module Hamming.App.Widgets.Internal (hammingW') where
+
+import Hamming.App.Types
+
+hammingW' :: AppState -> [[([String], String)]]
+hammingW' = undefined
+
+--jl