aboutsummaryrefslogtreecommitdiffhomepage
path: root/Main.hs
diff options
context:
space:
mode:
Diffstat (limited to 'Main.hs')
-rw-r--r--Main.hs55
1 files changed, 43 insertions, 12 deletions
diff --git a/Main.hs b/Main.hs
index e844eab..32d7616 100644
--- a/Main.hs
+++ b/Main.hs
@@ -1,30 +1,27 @@
{-# LANGUAGE OverloadedStrings #-}
-{-# LANGUAGE TemplateHaskell #-}
import Control.Monad (void)
import Data.Monoid
import qualified Graphics.Vty as V
import Lens.Micro ((&), (.~), (^.))
-import Lens.Micro.TH (makeLenses)
import Brick.AttrMap
import Brick.Main
+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.Widgets.Core
+import Data.Text.Markup ((@@))
-data St =
- St { _stExternalInput :: String
- }
-
-makeLenses ''St
+import Types
drawUI :: St -> [Widget ()]
drawUI st = [ui]
where
ui = vBox [ hBorderWithLabel (str "[ Status ]")
- , padAll 1 $ C.center $ status
+ , C.center $ status
, hBorderWithLabel (str "[ Current settings ]")
, padAll 1 $ C.center $ settings
, hBorderWithLabel (str "[ Presets ]")
@@ -33,20 +30,54 @@ drawUI st = [ui]
, padAll 1 $ C.center $ actions
]
status = str "Ready to scan first page"
- settings = str "settings"
- presets = str "presets"
+ settings = 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)
+ ]
+ presets = vBox [ markup $ ("h:" @@ (V.withStyle V.currentAttr V.bold))
+ <> (" handwritten notes" @@ fg V.white)
+ ]
actions = str "actions"
+appEvent :: St -> BrickEvent () e -> EventM () (Next St)
+appEvent st (VtyEvent e) =
+ case e of
+ -- settings toggles
+ V.EvKey (V.KChar 'o') [] -> continue $ st & stOCR .~ (not $ st^.stOCR)
+ V.EvKey (V.KChar 'c') [] -> continue $
+ st & stColour .~ (cycleColour $ st^.stColour)
+ V.EvKey (V.KChar 'p') [] -> continue $
+ st & stPaper .~ (cyclePaper $ st^.stPaper)
+
+ -- presets: set several settings toggles at once
+ V.EvKey (V.KChar 'h') [] -> continue $ st
+ { _stOCR = False
+ , _stColour = Greyscale
+ , _stDPI = 75
+ }
+
+ -- actions
+ V.EvKey (V.KChar 'q') [] -> halt st
+
+ _ -> continue st
+appEvent st _ = continue st
+
initialState :: St
initialState =
- St { _stExternalInput = ""
+ St { _stScanningSession = Nothing
+ , _stOCR = True
+ , _stColour = Greyscale
+ , _stPaper = A4
+ , _stDPI = 300
+ , _stOutdir = ""
}
theApp :: App St e ()
theApp =
App { appDraw = drawUI
, appChooseCursor = neverShowCursor
- , appHandleEvent = resizeOrQuit
+ , appHandleEvent = appEvent
, appStartEvent = return
, appAttrMap = const $ attrMap V.defAttr []
}