-
-
Notifications
You must be signed in to change notification settings - Fork 3.4k
Commit
This commit does not belong to any branch on this repository, and may belong to a fork outside of the repository.
- Loading branch information
Showing
6 changed files
with
65 additions
and
2 deletions.
There are no files selected for viewing
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters
Original file line number | Diff line number | Diff line change |
---|---|---|
@@ -0,0 +1,51 @@ | ||
{-# LANGUAGE RankNTypes #-} | ||
{-# LANGUAGE FlexibleInstances #-} | ||
{-# LANGUAGE UndecidableInstances #-} | ||
{-# LANGUAGE OverloadedStrings #-} | ||
{-# LANGUAGE LambdaCase #-} | ||
{-# LANGUAGE OverloadedLists #-} | ||
{-# LANGUAGE ScopedTypeVariables #-} | ||
|
||
{- | | ||
Module : Text.Pandoc.Readers.Djot | ||
Copyright : Copyright (C) 2024 John MacFarlane | ||
License : GNU GPL, version 2 or above | ||
Maintainer : John MacFarlane <[email protected]> | ||
Stability : alpha | ||
Portability : portable | ||
Reads and evaluates a Djot document as a Pandoc AST. | ||
-} | ||
module Text.Pandoc.Readers.Djot | ||
( readDjot | ||
) | ||
where | ||
|
||
import Text.Pandoc.Class | ||
import Text.Pandoc.Sources | ||
import Text.Parsec.Pos (sourceName) -- TODO export from T.P.Sources? | ||
import Text.Pandoc.Options | ||
import Text.Pandoc.Definition | ||
import qualified Text.Pandoc.UTF8 as UTF8 | ||
import Djot.Options (ParseOptions(..)) | ||
import Djot.Blocks (parseDoc) | ||
import qualified Djot.AST as D | ||
import Text.Pandoc.Error (PandocError(..)) | ||
import Control.Monad.Except (throwError) | ||
import qualified Data.Text as T | ||
|
||
-- import Debug.Trace | ||
|
||
-- | Read Djot from an input string and return a Pandoc document. | ||
readDjot :: (PandocMonad m, ToSources a) => ReaderOptions -> a -> m Pandoc | ||
readDjot _opts inp = do | ||
let sources = toSources inp | ||
let inputName = case sources of | ||
Sources ((pos, _):_) -> sourceName pos | ||
_ -> "" | ||
case parseDoc ParseOptions{ optSourcePositions = False } | ||
(UTF8.fromText $ sourcesToText sources) of | ||
Left e -> throwError $ PandocParseError $ T.pack $ show e | ||
Right doc -> do | ||
pure $ Pandoc mempty mempty -- TODO |
This file contains bidirectional Unicode text that may be interpreted or compiled differently than what appears below. To review, open the file in an editor that reveals hidden Unicode characters.
Learn more about bidirectional Unicode characters