From 1a48af859360e388c829f78ace708d32131d0a9b Mon Sep 17 00:00:00 2001 From: Sean Whitton Date: Sat, 25 Feb 2017 14:20:14 -0700 Subject: UI elements to toggle state --- Main.hs | 55 +++++++++++++++++++++++++++++++++++++++++++------------ Types.hs | 41 +++++++++++++++++++++++++++++++++++++++++ 2 files changed, 84 insertions(+), 12 deletions(-) create mode 100644 Types.hs 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 [] } diff --git a/Types.hs b/Types.hs new file mode 100644 index 0000000..721b00d --- /dev/null +++ b/Types.hs @@ -0,0 +1,41 @@ +{-# LANGUAGE TemplateHaskell #-} + +module Types where + +import Lens.Micro.TH (makeLenses) + +-- | Whether to do colour, grey or b&w scans +data Colour = Lineart | Greyscale | Colour + deriving (Eq, Show) + +cycleColour :: Colour -> Colour +cycleColour Lineart = Greyscale +cycleColour Greyscale = Colour +cycleColour Colour = Lineart + +-- | Paper size to scan (determines both scanning area and PDF page +-- size) +data Paper = A4 | Letter | Photo | Auto + deriving (Eq, Show) + +cyclePaper :: Paper -> Paper +cyclePaper A4 = Letter +cyclePaper Letter = Photo +cyclePaper Photo = Auto +cyclePaper Auto = A4 + +-- | DPI to scan +type DPI = Int + +data St = + St { _stScanningSession :: Maybe FilePath -- ^ if a session is in + -- progress, accmulate + -- scans in this dir + , _stOCR :: Bool -- ^ whether to use OCRmyPDF + , _stColour :: Colour + , _stPaper :: Paper + , _stDPI :: DPI + , _stOutdir :: FilePath -- ^ where to save final PDFs + } + +makeLenses ''St -- cgit v1.2.3