aboutsummaryrefslogtreecommitdiffhomepage
diff options
context:
space:
mode:
authorSean Whitton <spwhitton@spwhitton.name>2017-02-25 15:17:15 -0700
committerSean Whitton <spwhitton@spwhitton.name>2017-02-25 15:17:15 -0700
commitc4a2d0cdd5be556848627fb65d603e1fd5d66a2f (patch)
treef7d7fb54fb9beb5f0762fae86f660cf9f687b22a
parent3ced073c900ae0389771b438da3d0584a6dfec63 (diff)
downloadsscan-c4a2d0cdd5be556848627fb65d603e1fd5d66a2f.tar.gz
factor out defnList widget
-rw-r--r--Brick/Widgets/DefnList.hs13
-rw-r--r--Main.hs37
2 files changed, 32 insertions, 18 deletions
diff --git a/Brick/Widgets/DefnList.hs b/Brick/Widgets/DefnList.hs
new file mode 100644
index 0000000..5750cdc
--- /dev/null
+++ b/Brick/Widgets/DefnList.hs
@@ -0,0 +1,13 @@
+module Brick.Widgets.DefnList (defnList) where
+
+import Brick.Types
+import Brick.Widgets.Core
+
+defnList :: [(String, String)] -> Widget ()
+defnList defns = vBox $ line <$> defns
+ where
+ line (label, content) = str $
+ label ++ sep ++ (gap label content) ++ content
+ gap a b = take (maxWidth - length a - length b - length sep) $ repeat ' '
+ maxWidth = maximum $ map (\(x,y) -> length sep + length x + length y) defns
+ sep = ": "
diff --git a/Main.hs b/Main.hs
index 4ab6c93..21f1747 100644
--- a/Main.hs
+++ b/Main.hs
@@ -1,24 +1,25 @@
{-# LANGUAGE OverloadedStrings #-}
-import Control.Monad (void)
+import Control.Monad (void)
import Data.Monoid
-import qualified Graphics.Vty as V
-import Lens.Micro ((&), (.~), (^.))
-import qualified Data.Text as T
+import qualified Data.Text as T
+import qualified Graphics.Vty as V
+import Lens.Micro ((&), (.~), (^.))
import Brick.AttrMap
import Brick.Main
-import Brick.Markup (markup, (@?))
+import Brick.Markup (markup, (@?))
import Brick.Types
-import Brick.Util (fg, on)
-import Brick.Widgets.Border as B
-import Brick.Widgets.Center as C
+import Brick.Util (fg, on)
+import Brick.Widgets.Border as B
+import Brick.Widgets.Center as C
import Brick.Widgets.Core
-import Data.Text.Markup ((@@))
+import Data.Text.Markup ((@@))
+import Brick.Widgets.DefnList
import Presets
-import Types.State
import Types.Preset
+import Types.State
drawUI :: St -> [Widget ()]
drawUI st = [ui]
@@ -33,12 +34,12 @@ drawUI st = [ui]
, padAll 1 $ C.center $ actionsBox
]
status = str "Ready to scan first page"
- settingsBox = vBox [ str $ "run OCRmyPDF: "
- <> if st^.stOCR then "yes" else "no"
- , str $ "colour data: " ++ (show $ st^.stColour)
- , str $ "page size: " ++ (show $ st^.stPaper)
- , str $ "DPI: " ++ (show $ st^.stDPI)
- ]
+ settingsBox = defnList
+ [ ("run OCRmyPDF", if st^.stOCR then "yes" else "no")
+ , ("colour data", show $ st^.stColour)
+ , ("page size", show $ st^.stPaper)
+ , ("DPI", show $ st^.stDPI)
+ ]
presetsBox = vBox $
(\(Preset k desc _) ->
markup $
@@ -56,13 +57,13 @@ handleHotKey st 'p' = continue $
st & stPaper .~ (cyclePaper $ st^.stPaper)
handleHotKey st c = case lookupPreset c of
Just (Preset _ _ f) -> continue $ f st
- _ -> continue st
+ _ -> continue st
appEvent :: St -> BrickEvent () e -> EventM () (Next St)
appEvent st (VtyEvent e) =
case e of
V.EvKey (V.KChar c) [] -> handleHotKey st c
- _ -> continue st
+ _ -> continue st
appEvent st _ = continue st
initialState :: St