From 0ad235d3f0f117e5cf48edb21d1d8297f38d05eb Mon Sep 17 00:00:00 2001 From: Yvee1 Date: Sun, 26 Jan 2020 22:58:47 +0100 Subject: [PATCH] Add selection to multiple choice question. --- cards/example.txt | 15 +++++------ src/Lib.hs | 65 +++++++++++++++++++++++++++++++++++------------ 2 files changed, 56 insertions(+), 24 deletions(-) diff --git a/cards/example.txt b/cards/example.txt index 1c4a5d9..a129d67 100644 --- a/cards/example.txt +++ b/cards/example.txt @@ -1,3 +1,10 @@ +# Multiple choice question, (only one answer is right) +- Option 1 +* Option 2 (this is the correct answer) +- Option 3 +- Option 4 + +--- # ipRGC intrinsically photosensitive Retinal Ganglion Cell @@ -5,12 +12,4 @@ intrinsically photosensitive Retinal Ganglion Cell # Retina Part of the eye that turns light into electrical neural impulses. ---- - -# Multiple choice question, (only one answer is right) -- Option 1 -* Option 2 (this is the correct answer) -- Option 3 -- Option 4 - --- \ No newline at end of file diff --git a/src/Lib.hs b/src/Lib.hs index 00469c0..8d4dfb0 100644 --- a/src/Lib.hs +++ b/src/Lib.hs @@ -1,4 +1,5 @@ {-# LANGUAGE TemplateHaskell #-} + module Lib where import System.IO (stdin, hReady, hSetEcho, hSetBuffering, BufferMode(NoBuffering)) @@ -11,17 +12,30 @@ import qualified Brick.Widgets.Border.Style as BS import qualified Brick.Widgets.Center as C import qualified Graphics.Vty as V -data State = State - { _cards :: [Card] -- list of flashcards - , _index :: Int -- current card index - , _correct :: Int -- not implemented, but for score keeping - } - -makeLenses ''State - type Event = () type Name = () +data CardState = + DefinitionState + { _flipped :: Bool } + | MultipleChoiceState + { _selected :: Int + , _nChoices :: Int } + +data State = State + { _cards :: [Card] -- list of flashcards + , _index :: Int -- current card index + , _currentCard :: Card + , _cardState :: CardState + } + +makeLenses ''CardState +makeLenses ''State + +defaultCardState :: Card -> CardState +defaultCardState Definition{} = DefinitionState { _flipped = False } +defaultCardState (MultipleChoice _ _ ics) = MultipleChoiceState { _selected = 0, _nChoices = length ics + 1} + app :: App State Event Name app = App { appDraw = drawUI @@ -44,8 +58,8 @@ drawDescr :: String -> Widget Name drawDescr descr = padLeftRight 1 $ strWrap descr -listMultipleChoice :: CorrectOption -> [IncorrectOption] -> String -listMultipleChoice c = concat . reverse . listMultipleChoice' [] 0 c +listMultipleChoice :: CorrectOption -> [IncorrectOption] -> [String] +listMultipleChoice c = reverse . listMultipleChoice' [] 0 c where listMultipleChoice' opts i c@(CorrectOption j cStr) [] = if i == j then cStr : opts @@ -62,7 +76,14 @@ drawCardUI s = drawHeader title <=> drawDescr descr MultipleChoice question correct others -> drawCardBox $ - drawHeader question <=> drawDescr (listMultipleChoice correct others) + drawHeader question <=> drawOptions (listMultipleChoice correct others) s + +drawOptions :: [String] -> State -> Widget Name +drawOptions options s = case s ^. cardState of + MultipleChoiceState i _ -> drawDescr (concat formattedOptions) + -- Add "* " to the beginning of selected option + where formattedOptions = options & ix i %~ ("* "++) + _ -> error "impossible" drawCardBox :: Widget Name -> Widget Name drawCardBox w = C.center $ @@ -79,8 +100,16 @@ handleEvent s (VtyEvent (V.EvKey V.KEnter [])) = next s handleEvent s (VtyEvent (V.EvKey V.KRight [])) = next s handleEvent s (VtyEvent (V.EvKey (V.KChar ' ') [])) = next s handleEvent s (VtyEvent (V.EvKey V.KLeft [])) = previous s +handleEvent s (VtyEvent (V.EvKey V.KUp [])) = continue $ + case s ^. cardState of + MultipleChoiceState i _ -> if i > 0 then s & (cardState.selected) -~ 1 else s + _ -> s +handleEvent s (VtyEvent (V.EvKey V.KDown [])) = continue $ + case s ^. cardState of + MultipleChoiceState i nChoices -> if i < nChoices - 1 then s & (cardState.selected) +~ 1 else s + _ -> s handleEvent s _ = continue s - + titleAttr :: AttrName titleAttr = attrName "title" @@ -89,8 +118,8 @@ textboxAttr = attrName "textbox" theMap :: AttrMap theMap = attrMap V.defAttr - [(titleAttr, bg V.green `V.withStyle` V.bold `V.withStyle` V.underline) - ,(textboxAttr, V.defAttr) + [ (titleAttr, bg V.green `V.withStyle` V.bold `V.withStyle` V.underline) + , (textboxAttr, V.defAttr) ] handleFilePath :: FilePath -> IO String @@ -101,7 +130,10 @@ runBrickFlashcards input = do let cards = case parseCards input of Left parseError -> error (show parseError) Right result -> result - let initialState = State cards 0 0 + let initialState = State { _cards = cards + , _index = 0 + , _currentCard = head cards + , _cardState = defaultCardState (head cards)} finalState <- defaultMain app initialState pure () @@ -113,4 +145,5 @@ next s = if (s ^. index + 1) < length (s ^. cards) previous :: State -> EventM Name (Next State) previous s | s ^. index > 0 = continue $ s & index %~ subtract 1 - | otherwise = continue s \ No newline at end of file + | otherwise = continue s +