1
1
mirror of https://github.com/Yvee1/hascard.git synced 2024-10-05 19:49:16 +03:00

Add basic LaTeX support

This commit is contained in:
Steven van den Broek 2020-11-14 16:07:33 +01:00
parent c5ac75ca6f
commit 3a84eaad89
7 changed files with 75 additions and 42 deletions

View File

@ -0,0 +1,18 @@
# What type of fruit is this?
![](pear.jpeg)
- Apple
* Pear
- Orange
- Banana
---
# Is the following statement true?
![](lp.pdf)
- No
* Yes
---
# The l^p metric space
```
The space $(\ell^p, d)$ is a metric space, when $d:\ell^p \times \ell^p \rightarrow \mathbb{R}$ is defined as
$$d(x, y) = \left(\sum_{n=1}^\infty |x_n-y_n|^p\right)^{1/p}$$
```
---

View File

@ -1,15 +0,0 @@
# What type of fruit is this?
![](pear.jpeg)
- Apple
* Pear
- Orange
- Banana
---
# Fruit 1
![](pear.jpeg)
This is a pear
---
# Is the following statement true?
![](lp.pdf)
- No
* Yes

View File

@ -41,7 +41,7 @@ pHeader = do
spaceChar spaceChar
many (noneOf ['\n', '\r']) many (noneOf ['\n', '\r'])
pImage :: Parser Image pImage :: Parser External
pImage = do pImage = do
many eol many eol
char '!' char '!'
@ -51,14 +51,21 @@ pImage = do
img <- manyTill anySingle (char ')') img <- manyTill anySingle (char ')')
return $ Image alt img return $ Image alt img
pMaybeImage :: Parser (Maybe Image) pLatex :: Parser External
pMaybeImage = Just <$> try pImage pLatex = do
<|> pure Nothing many eol
string "```"
Latex <$> manyTill anySingle (try (string "```"))
pMaybeExternal :: Parser (Maybe External)
pMaybeExternal = Just <$> try pImage
<|> Just <$> try pLatex
<|> pure Nothing
pMultChoice :: CardParser pMultChoice :: CardParser
pMultChoice = do pMultChoice = do
header <- pHeader header <- pHeader
img <- pMaybeImage img <- pMaybeExternal
many eol many eol
choices <- pChoice `sepBy1` lookAhead (try choicePrefix) choices <- pChoice `sepBy1` lookAhead (try choicePrefix)
msgOrResult <- makeMultipleChoice choices msgOrResult <- makeMultipleChoice choices
@ -81,7 +88,7 @@ choicePrefix = string "- "
pMultAnswer :: CardParser pMultAnswer :: CardParser
pMultAnswer = do pMultAnswer = do
header <- pHeader header <- pHeader
img <- pMaybeImage img <- pMaybeExternal
many eol many eol
options <- pOption `sepBy1` lookAhead (try (char '[')) options <- pOption `sepBy1` lookAhead (try (char '['))
return . Right $ MultipleAnswer header img (NE.fromList options) return . Right $ MultipleAnswer header img (NE.fromList options)
@ -97,7 +104,7 @@ pOption = do
pReorder :: CardParser pReorder :: CardParser
pReorder = do pReorder = do
header <- pHeader header <- pHeader
img <- pMaybeImage img <- pMaybeExternal
many eol many eol
elements <- pReorderElement `sepBy1` lookAhead (try pReorderPrefix) elements <- pReorderElement `sepBy1` lookAhead (try pReorderPrefix)
let numbers = map fst elements let numbers = map fst elements
@ -122,7 +129,7 @@ pReorderPrefix = do
pOpen :: CardParser pOpen :: CardParser
pOpen = do pOpen = do
header <- pHeader header <- pHeader
img <- pMaybeImage img <- pMaybeExternal
many eol many eol
(pre, gap) <- pGap (pre, gap) <- pGap
sentence <- pSentence sentence <- pSentence
@ -161,7 +168,7 @@ pNormal = do
pDef :: CardParser pDef :: CardParser
pDef = do pDef = do
header <- pHeader header <- pHeader
img <- pMaybeImage img <- pMaybeExternal
many eol many eol
descr <- manyTill chars $ lookAhead $ try $ seperator <|> eof' descr <- manyTill chars $ lookAhead $ try $ seperator <|> eof'
return $ Right (Definition header img (dropWhileEnd isSpace' descr)) return $ Right (Definition header img (dropWhileEnd isSpace' descr))

View File

@ -64,7 +64,7 @@ cardsState doReview fp deck = do
, _popup = Nothing , _popup = Nothing
, _pathToFile = fp } , _pathToFile = fp }
openCardImage (takeDirectory fp) firstCard openCardExternal (takeDirectory fp) firstCard
return $ CardsState initialState return $ CardsState initialState
cardsWithOptionsState :: GlobalState -> FilePath -> [Card] -> IO State cardsWithOptionsState :: GlobalState -> FilePath -> [Card] -> IO State

View File

@ -3,32 +3,33 @@ import Data.Functor
import Data.List import Data.List
import Data.List.NonEmpty (NonEmpty) import Data.List.NonEmpty (NonEmpty)
import System.FilePath import System.FilePath
import System.Process (runCommand) import System.Process
import System.Info import System.Info
import System.IO
import qualified Data.List.NonEmpty as NE import qualified Data.List.NonEmpty as NE
import qualified System.Directory as D import qualified System.Directory as D
-- Word Description -- Word Description
data Card = Definition { data Card = Definition {
question :: String, question :: String,
image :: Maybe Image, external :: Maybe External,
definition :: String } definition :: String }
| OpenQuestion { | OpenQuestion {
question :: String, question :: String,
image :: Maybe Image, external :: Maybe External,
perforated :: Perforated } perforated :: Perforated }
| MultipleChoice { | MultipleChoice {
question :: String, question :: String,
image :: Maybe Image, external :: Maybe External,
correct :: CorrectOption, correct :: CorrectOption,
incorrects :: [IncorrectOption]} incorrects :: [IncorrectOption]}
| MultipleAnswer { | MultipleAnswer {
question :: String, question :: String,
image :: Maybe Image, external :: Maybe External,
options :: NonEmpty Option } options :: NonEmpty Option }
| Reorder { | Reorder {
question :: String, question :: String,
image :: Maybe Image, external :: Maybe External,
elements :: NonEmpty (Int, String) elements :: NonEmpty (Int, String)
} }
@ -44,11 +45,13 @@ instance Show Card where
Reorder h img elts -> Reorder h img elts ->
showHeader h <> show img<> "\n" <> unlines' (NE.toList (NE.map showReorder elts)) showHeader h <> show img<> "\n" <> unlines' (NE.toList (NE.map showReorder elts))
-- alt file -- alt file
data Image = Image String String data External = Image String String
| Latex String
instance Show Image where instance Show External where
show (Image alt file) = "![" <> alt <> "]" <> "(" <> file <> ")" show (Image alt file) = "![" <> alt <> "]" <> "(" <> file <> ")"
show (Latex text) = "```\n" <> text <> "```"
openCommand :: String openCommand :: String
openCommand = case os of openCommand = case os of
@ -56,8 +59,8 @@ openCommand = case os of
"linux" -> "xdg-open" "linux" -> "xdg-open"
_ -> error "Unkown OS for opening images" _ -> error "Unkown OS for opening images"
openImage :: FilePath -> Image -> IO () openImage :: FilePath -> FilePath -> IO ()
openImage origin (Image _ relative) = openImage' (origin </> relative) openImage origin relative = openImage' (origin </> relative)
openImage' :: FilePath -> IO () openImage' :: FilePath -> IO ()
openImage' fp = do openImage' fp = do
@ -66,8 +69,28 @@ openImage' fp = do
then void $ runCommand (openCommand <> " \"" <> fp <> "\"") then void $ runCommand (openCommand <> " \"" <> fp <> "\"")
else error $ "The image you were trying to open does not exist: " <> fp else error $ "The image you were trying to open does not exist: " <> fp
openCardImage :: FilePath -> Card -> IO () openLatex :: String -> IO ()
openCardImage fp = flip whenJust (openImage fp) . image openLatex latex = do
let packages = ["amsfonts", "mathtools"]
text = unlines $
[ "\\documentclass[preview]{standalone}" ]
++ map (\p -> "\\usepackage{"<>p<>"}") packages ++
[ "\\begin{document}"
, latex
, "\\end{document}" ]
dir <- D.getTemporaryDirectory
(tempfile, temph) <- openTempFile dir "hascard-latex-"
hPutStrLn temph text
hClose temph
callProcess "pdflatex" ["-output-directory", dir, tempfile]
openImage' (tempfile <> ".pdf")
openCardExternal :: FilePath -> Card -> IO ()
openCardExternal origin card =
case external card of
Nothing -> pure ()
Just (Image _ relative) -> openImage origin relative
Just (Latex text) -> openLatex text
whenJust :: Applicative m => Maybe a -> (a -> m ()) -> m () whenJust :: Applicative m => Maybe a -> (a -> m ()) -> m ()
whenJust mg f = maybe (pure ()) f mg whenJust mg f = maybe (pure ()) f mg

View File

@ -6,7 +6,7 @@ module UI
, GenIO , GenIO
, Chunk(..) , Chunk(..)
, Card , Card
, Image , External
, ImportType(..) , ImportType(..)
, Parameters(..) , Parameters(..)
@ -27,7 +27,7 @@ import Glue
import Import import Import
import States import States
import StateManagement import StateManagement
import Types (Card, Image, cardsToString) import Types (Card, External, cardsToString)
runBrickFlashcards :: GlobalState -> IO () runBrickFlashcards :: GlobalState -> IO ()
runBrickFlashcards gs = do runBrickFlashcards gs = do

View File

@ -418,7 +418,7 @@ handleEvent gs _ _ = continue gs
next :: GlobalState -> CS -> EventM Name (Next GlobalState) next :: GlobalState -> CS -> EventM Name (Next GlobalState)
next gs s next gs s
| s ^. index + 1 < length (s ^. cards) = liftIO (openCardImage (takeDirectory (s^.pathToFile)) ((s^.cards) !! (s^.index + 1))) *> (continue . updateCS gs . straightenState $ s & index +~ 1) | s ^. index + 1 < length (s ^. cards) = liftIO (openCardExternal (takeDirectory (s^.pathToFile)) ((s^.cards) !! (s^.index + 1))) *> (continue . updateCS gs . straightenState $ s & index +~ 1)
| s ^. reviewMode = | s ^. reviewMode =
let thePopup = let thePopup =
if null (s^.correctCards) || length (s^. correctCards) == length (s^.cards) if null (s^.correctCards) || length (s^. correctCards) == length (s^.cards)
@ -428,7 +428,7 @@ next gs s
| otherwise = halt' gs | otherwise = halt' gs
previous :: GlobalState -> CS -> EventM Name (Next GlobalState) previous :: GlobalState -> CS -> EventM Name (Next GlobalState)
previous gs s | s ^. index > 0 = continue . updateCS gs . straightenState $ s & index -~ 1 previous gs s | s ^. index > 0 = liftIO (openCardExternal (takeDirectory (s^.pathToFile)) ((s^.cards) !! (s^.index - 1))) *> (continue . updateCS gs . straightenState $ s & index -~ 1)
| otherwise = continue gs | otherwise = continue gs
straightenState :: CS -> CS straightenState :: CS -> CS