Skip to content

Commit

Permalink
Refactor
Browse files Browse the repository at this point in the history
  • Loading branch information
jaspervdj committed Oct 26, 2024
1 parent 17c847d commit 7bceea4
Show file tree
Hide file tree
Showing 5 changed files with 30 additions and 26 deletions.
23 changes: 8 additions & 15 deletions lib/Patat/Eval.hs
Original file line number Diff line number Diff line change
Expand Up @@ -4,7 +4,6 @@
module Patat.Eval
( parseEvalBlocks

, UpdateVar
, updateVar
, evalVar
, evalVars
Expand Down Expand Up @@ -109,20 +108,14 @@ evalBlock _ block =
pure [Append [block]]


--------------------------------------------------------------------------------
data UpdateVar = UpdateVar Int Var [Pandoc.Block]
deriving (Eq, Show)


--------------------------------------------------------------------------------
updateVar ::UpdateVar -> Presentation -> Presentation
updateVar (UpdateVar version var out) pres
| version /= pVersion pres = pres
| otherwise = pres {pVars = HMS.insert var out $ pVars pres}
updateVar :: Var -> [Pandoc.Block] -> Presentation -> Presentation
updateVar var blocks pres = pres {pVars = HMS.insert var blocks $ pVars pres}


--------------------------------------------------------------------------------
evalVar :: Var -> (UpdateVar -> IO ()) -> Presentation -> IO Presentation
evalVar :: Var -> ([Pandoc.Block] -> IO ()) -> Presentation -> IO Presentation
evalVar var writeOutput presentation = case HMS.lookup var evalBlocks of
Nothing -> pure presentation
Just EvalBlock {..} | Just _ <- ebAsync -> pure presentation
Expand All @@ -134,8 +127,7 @@ evalVar var writeOutput presentation = case HMS.lookup var evalBlocks of
t <- IORef.atomicModifyIORef' outRef $ \o ->
let n = if T.null o then l else o <> "\n" <> l in
(n, n)
writeOutput $ UpdateVar (pVersion presentation) var
(renderEvalBlock eb t)
writeOutput $ renderEvalBlock eb t

let copyLines h = catch
(forever $ do
Expand Down Expand Up @@ -172,9 +164,10 @@ evalVar var writeOutput presentation = case HMS.lookup var evalBlocks of
--------------------------------------------------------------------------------
evalVars
:: Foldable f
=> f Var -> (UpdateVar -> IO ()) -> Presentation -> IO Presentation
=> f Var -> (Var -> [Pandoc.Block] -> IO ()) -> Presentation
-> IO Presentation
evalVars vars update presentation =
foldM (\p var -> evalVar var update p) presentation vars
foldM (\p var -> evalVar var (update var) p) presentation vars


--------------------------------------------------------------------------------
Expand All @@ -192,6 +185,6 @@ forceEval pres = do
Just eb -> do
for_ (ebAsync eb) Async.wait
IORef.atomicModifyIORef' updates $ \l ->
([], foldl' (\p u -> updateVar u p) pres1 l)
([], foldl' (\p u -> updateVar var u p) pres1 l)

foldM forceEvalVar pres (HMS.keys (pEvalBlocks pres))
3 changes: 2 additions & 1 deletion lib/Patat/Main.hs
Original file line number Diff line number Diff line change
Expand Up @@ -213,7 +213,8 @@ loop app@App {..} = do
-- Start necessary eval blocks
presentation <- Eval.evalVars
(activeVars aPresentation)
(Chan.writeChan aCommandChan . PresentationCommand . UpdateVar)
(\var blocks -> Chan.writeChan aCommandChan $ PresentationCommand $
UpdateVar (pVersion aPresentation) var blocks)
aPresentation

size <- getPresentationSize presentation
Expand Down
19 changes: 12 additions & 7 deletions lib/Patat/Presentation/Interactive.hs
Original file line number Diff line number Diff line change
Expand Up @@ -13,12 +13,14 @@ module Patat.Presentation.Interactive


--------------------------------------------------------------------------------
import Data.Char (isDigit)
import qualified Patat.Eval as Eval
import Data.Char (isDigit)
import qualified Patat.Eval as Eval
import Patat.Presentation.Instruction (Var)
import Patat.Presentation.Internal
import Patat.Presentation.Read
import qualified System.IO as IO
import Text.Read (readMaybe)
import qualified System.IO as IO
import qualified Text.Pandoc as Pandoc
import Text.Read (readMaybe)


--------------------------------------------------------------------------------
Expand All @@ -32,7 +34,7 @@ data PresentationCommand
| Last
| Reload
| Seek Int
| UpdateVar Eval.UpdateVar
| UpdateVar Version Var [Pandoc.Block]
| UnknownCommand String
deriving (Eq, Show)

Expand Down Expand Up @@ -107,12 +109,15 @@ updatePresentation cmd presentation = case cmd of
Last -> pure $ goToSlide $ \_ -> (numSlides presentation, 0)
Seek n -> pure $ goToSlide $ \_ -> (n - 1, 0)
Reload -> reloadPresentation
UpdateVar u -> pure $ UpdatedPresentation $ Eval.updateVar u presentation
UnknownCommand _ -> pure $ UpdatedPresentation presentation
UpdateVar v x b -> pure $ UpdatedPresentation $
if v /= version then presentation else Eval.updateVar x b presentation
where
numSlides :: Presentation -> Int
numSlides pres = length (pSlides pres)

version = pVersion presentation

clip :: Index -> Presentation -> Index
clip (slide, fragment) pres
| slide >= numSlides pres = (numSlides pres - 1, lastFragments - 1)
Expand Down Expand Up @@ -140,6 +145,6 @@ updatePresentation cmd presentation = case cmd of
return $ case errOrPres of
Left err -> ErroredPresentation err
Right pres -> UpdatedPresentation $ pres
{ pVersion = pVersion presentation + 1
{ pVersion = Version (unVersion version + 1)
, pActiveFragment = clip (pActiveFragment presentation) pres
}
9 changes: 7 additions & 2 deletions lib/Patat/Presentation/Internal.hs
Original file line number Diff line number Diff line change
Expand Up @@ -3,7 +3,8 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
module Patat.Presentation.Internal
( Breadcrumbs
( Version (..)
, Breadcrumbs
, Presentation (..)
, PresentationSettings (..)
, defaultPresentationSettings
Expand Down Expand Up @@ -60,14 +61,18 @@ import qualified Skylighting as Skylighting
import qualified Text.Pandoc as Pandoc


--------------------------------------------------------------------------------
newtype Version = Version {unVersion :: Int} deriving (Eq, Show)


--------------------------------------------------------------------------------
type Breadcrumbs = [(Int, [Pandoc.Inline])]


--------------------------------------------------------------------------------
data Presentation = Presentation
{ pFilePath :: !FilePath
, pVersion :: !Int
, pVersion :: !Version
, pEncodingFallback :: !EncodingFallback
, pTitle :: ![Pandoc.Inline]
, pAuthor :: ![Pandoc.Inline]
Expand Down
2 changes: 1 addition & 1 deletion lib/Patat/Presentation/Read.hs
Original file line number Diff line number Diff line change
Expand Up @@ -126,7 +126,7 @@ pandocToPresentation
-> Skylighting.SyntaxMap -> Pandoc.Pandoc -> Either String Presentation
pandocToPresentation pFilePath pEncodingFallback pSettings pSyntaxMap
pandoc@(Pandoc.Pandoc meta _) = do
let !pVersion = 0
let !pVersion = Version 0
!pTitle = case Pandoc.docTitle meta of
[] -> [Pandoc.Str . T.pack . snd $ splitFileName pFilePath]
title -> title
Expand Down

0 comments on commit 7bceea4

Please sign in to comment.