1
1
mirror of https://github.com/Yvee1/hascard.git synced 2024-11-25 20:33:34 +03:00

Add selection to multiple choice question.

This commit is contained in:
Yvee1 2020-01-26 22:58:47 +01:00
parent 3361c9f8f1
commit 0ad235d3f0
2 changed files with 56 additions and 24 deletions

View File

@ -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 # ipRGC
intrinsically photosensitive Retinal Ganglion Cell intrinsically photosensitive Retinal Ganglion Cell
@ -6,11 +13,3 @@ intrinsically photosensitive Retinal Ganglion Cell
Part of the eye that turns light into electrical neural impulses. 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
---

View File

@ -1,4 +1,5 @@
{-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE TemplateHaskell #-}
module Lib where module Lib where
import System.IO (stdin, hReady, hSetEcho, hSetBuffering, BufferMode(NoBuffering)) 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 Brick.Widgets.Center as C
import qualified Graphics.Vty as V 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 Event = ()
type Name = () 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 State Event Name
app = App app = App
{ appDraw = drawUI { appDraw = drawUI
@ -44,8 +58,8 @@ drawDescr :: String -> Widget Name
drawDescr descr = padLeftRight 1 $ drawDescr descr = padLeftRight 1 $
strWrap descr strWrap descr
listMultipleChoice :: CorrectOption -> [IncorrectOption] -> String listMultipleChoice :: CorrectOption -> [IncorrectOption] -> [String]
listMultipleChoice c = concat . reverse . listMultipleChoice' [] 0 c listMultipleChoice c = reverse . listMultipleChoice' [] 0 c
where listMultipleChoice' opts i c@(CorrectOption j cStr) [] = where listMultipleChoice' opts i c@(CorrectOption j cStr) [] =
if i == j if i == j
then cStr : opts then cStr : opts
@ -62,7 +76,14 @@ drawCardUI s =
drawHeader title <=> drawDescr descr drawHeader title <=> drawDescr descr
MultipleChoice question correct others -> drawCardBox $ 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 :: Widget Name -> Widget Name
drawCardBox w = C.center $ drawCardBox w = C.center $
@ -79,6 +100,14 @@ handleEvent s (VtyEvent (V.EvKey V.KEnter [])) = next s
handleEvent s (VtyEvent (V.EvKey V.KRight [])) = 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.KChar ' ') [])) = next s
handleEvent s (VtyEvent (V.EvKey V.KLeft [])) = previous 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 handleEvent s _ = continue s
titleAttr :: AttrName titleAttr :: AttrName
@ -89,8 +118,8 @@ textboxAttr = attrName "textbox"
theMap :: AttrMap theMap :: AttrMap
theMap = attrMap V.defAttr theMap = attrMap V.defAttr
[(titleAttr, bg V.green `V.withStyle` V.bold `V.withStyle` V.underline) [ (titleAttr, bg V.green `V.withStyle` V.bold `V.withStyle` V.underline)
,(textboxAttr, V.defAttr) , (textboxAttr, V.defAttr)
] ]
handleFilePath :: FilePath -> IO String handleFilePath :: FilePath -> IO String
@ -101,7 +130,10 @@ runBrickFlashcards input = do
let cards = case parseCards input of let cards = case parseCards input of
Left parseError -> error (show parseError) Left parseError -> error (show parseError)
Right result -> result 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 finalState <- defaultMain app initialState
pure () pure ()
@ -114,3 +146,4 @@ next s = if (s ^. index + 1) < length (s ^. cards)
previous :: State -> EventM Name (Next State) previous :: State -> EventM Name (Next State)
previous s | s ^. index > 0 = continue $ s & index %~ subtract 1 previous s | s ^. index > 0 = continue $ s & index %~ subtract 1
| otherwise = continue s | otherwise = continue s