mirror of
https://github.com/Yvee1/hascard.git
synced 2024-11-22 04:33:06 +03:00
Add basic LaTeX support
This commit is contained in:
parent
c5ac75ca6f
commit
3a84eaad89
18
cards/images-and-formulas.txt
Normal file
18
cards/images-and-formulas.txt
Normal 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}$$
|
||||
```
|
||||
---
|
@ -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
|
@ -41,7 +41,7 @@ pHeader = do
|
||||
spaceChar
|
||||
many (noneOf ['\n', '\r'])
|
||||
|
||||
pImage :: Parser Image
|
||||
pImage :: Parser External
|
||||
pImage = do
|
||||
many eol
|
||||
char '!'
|
||||
@ -51,14 +51,21 @@ pImage = do
|
||||
img <- manyTill anySingle (char ')')
|
||||
return $ Image alt img
|
||||
|
||||
pMaybeImage :: Parser (Maybe Image)
|
||||
pMaybeImage = Just <$> try pImage
|
||||
<|> pure Nothing
|
||||
pLatex :: Parser External
|
||||
pLatex = do
|
||||
many eol
|
||||
string "```"
|
||||
Latex <$> manyTill anySingle (try (string "```"))
|
||||
|
||||
pMaybeExternal :: Parser (Maybe External)
|
||||
pMaybeExternal = Just <$> try pImage
|
||||
<|> Just <$> try pLatex
|
||||
<|> pure Nothing
|
||||
|
||||
pMultChoice :: CardParser
|
||||
pMultChoice = do
|
||||
header <- pHeader
|
||||
img <- pMaybeImage
|
||||
img <- pMaybeExternal
|
||||
many eol
|
||||
choices <- pChoice `sepBy1` lookAhead (try choicePrefix)
|
||||
msgOrResult <- makeMultipleChoice choices
|
||||
@ -81,7 +88,7 @@ choicePrefix = string "- "
|
||||
pMultAnswer :: CardParser
|
||||
pMultAnswer = do
|
||||
header <- pHeader
|
||||
img <- pMaybeImage
|
||||
img <- pMaybeExternal
|
||||
many eol
|
||||
options <- pOption `sepBy1` lookAhead (try (char '['))
|
||||
return . Right $ MultipleAnswer header img (NE.fromList options)
|
||||
@ -97,7 +104,7 @@ pOption = do
|
||||
pReorder :: CardParser
|
||||
pReorder = do
|
||||
header <- pHeader
|
||||
img <- pMaybeImage
|
||||
img <- pMaybeExternal
|
||||
many eol
|
||||
elements <- pReorderElement `sepBy1` lookAhead (try pReorderPrefix)
|
||||
let numbers = map fst elements
|
||||
@ -122,7 +129,7 @@ pReorderPrefix = do
|
||||
pOpen :: CardParser
|
||||
pOpen = do
|
||||
header <- pHeader
|
||||
img <- pMaybeImage
|
||||
img <- pMaybeExternal
|
||||
many eol
|
||||
(pre, gap) <- pGap
|
||||
sentence <- pSentence
|
||||
@ -161,7 +168,7 @@ pNormal = do
|
||||
pDef :: CardParser
|
||||
pDef = do
|
||||
header <- pHeader
|
||||
img <- pMaybeImage
|
||||
img <- pMaybeExternal
|
||||
many eol
|
||||
descr <- manyTill chars $ lookAhead $ try $ seperator <|> eof'
|
||||
return $ Right (Definition header img (dropWhileEnd isSpace' descr))
|
||||
|
@ -64,7 +64,7 @@ cardsState doReview fp deck = do
|
||||
, _popup = Nothing
|
||||
, _pathToFile = fp }
|
||||
|
||||
openCardImage (takeDirectory fp) firstCard
|
||||
openCardExternal (takeDirectory fp) firstCard
|
||||
return $ CardsState initialState
|
||||
|
||||
cardsWithOptionsState :: GlobalState -> FilePath -> [Card] -> IO State
|
||||
|
49
src/Types.hs
49
src/Types.hs
@ -3,32 +3,33 @@ import Data.Functor
|
||||
import Data.List
|
||||
import Data.List.NonEmpty (NonEmpty)
|
||||
import System.FilePath
|
||||
import System.Process (runCommand)
|
||||
import System.Process
|
||||
import System.Info
|
||||
import System.IO
|
||||
import qualified Data.List.NonEmpty as NE
|
||||
import qualified System.Directory as D
|
||||
|
||||
-- Word Description
|
||||
data Card = Definition {
|
||||
question :: String,
|
||||
image :: Maybe Image,
|
||||
external :: Maybe External,
|
||||
definition :: String }
|
||||
| OpenQuestion {
|
||||
question :: String,
|
||||
image :: Maybe Image,
|
||||
external :: Maybe External,
|
||||
perforated :: Perforated }
|
||||
| MultipleChoice {
|
||||
question :: String,
|
||||
image :: Maybe Image,
|
||||
external :: Maybe External,
|
||||
correct :: CorrectOption,
|
||||
incorrects :: [IncorrectOption]}
|
||||
| MultipleAnswer {
|
||||
question :: String,
|
||||
image :: Maybe Image,
|
||||
external :: Maybe External,
|
||||
options :: NonEmpty Option }
|
||||
| Reorder {
|
||||
question :: String,
|
||||
image :: Maybe Image,
|
||||
external :: Maybe External,
|
||||
elements :: NonEmpty (Int, String)
|
||||
}
|
||||
|
||||
@ -44,11 +45,13 @@ instance Show Card where
|
||||
Reorder h img elts ->
|
||||
showHeader h <> show img<> "\n" <> unlines' (NE.toList (NE.map showReorder elts))
|
||||
|
||||
-- alt file
|
||||
data Image = Image String String
|
||||
-- alt file
|
||||
data External = Image String String
|
||||
| Latex String
|
||||
|
||||
instance Show Image where
|
||||
instance Show External where
|
||||
show (Image alt file) = "![" <> alt <> "]" <> "(" <> file <> ")"
|
||||
show (Latex text) = "```\n" <> text <> "```"
|
||||
|
||||
openCommand :: String
|
||||
openCommand = case os of
|
||||
@ -56,8 +59,8 @@ openCommand = case os of
|
||||
"linux" -> "xdg-open"
|
||||
_ -> error "Unkown OS for opening images"
|
||||
|
||||
openImage :: FilePath -> Image -> IO ()
|
||||
openImage origin (Image _ relative) = openImage' (origin </> relative)
|
||||
openImage :: FilePath -> FilePath -> IO ()
|
||||
openImage origin relative = openImage' (origin </> relative)
|
||||
|
||||
openImage' :: FilePath -> IO ()
|
||||
openImage' fp = do
|
||||
@ -66,8 +69,28 @@ openImage' fp = do
|
||||
then void $ runCommand (openCommand <> " \"" <> fp <> "\"")
|
||||
else error $ "The image you were trying to open does not exist: " <> fp
|
||||
|
||||
openCardImage :: FilePath -> Card -> IO ()
|
||||
openCardImage fp = flip whenJust (openImage fp) . image
|
||||
openLatex :: String -> IO ()
|
||||
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 mg f = maybe (pure ()) f mg
|
||||
|
@ -6,7 +6,7 @@ module UI
|
||||
, GenIO
|
||||
, Chunk(..)
|
||||
, Card
|
||||
, Image
|
||||
, External
|
||||
, ImportType(..)
|
||||
, Parameters(..)
|
||||
|
||||
@ -27,7 +27,7 @@ import Glue
|
||||
import Import
|
||||
import States
|
||||
import StateManagement
|
||||
import Types (Card, Image, cardsToString)
|
||||
import Types (Card, External, cardsToString)
|
||||
|
||||
runBrickFlashcards :: GlobalState -> IO ()
|
||||
runBrickFlashcards gs = do
|
||||
|
@ -418,7 +418,7 @@ handleEvent gs _ _ = continue gs
|
||||
|
||||
next :: GlobalState -> CS -> EventM Name (Next GlobalState)
|
||||
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 =
|
||||
let thePopup =
|
||||
if null (s^.correctCards) || length (s^. correctCards) == length (s^.cards)
|
||||
@ -428,7 +428,7 @@ next gs s
|
||||
| otherwise = halt' gs
|
||||
|
||||
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
|
||||
|
||||
straightenState :: CS -> CS
|
||||
|
Loading…
Reference in New Issue
Block a user