module Dhall.Docs.Markdown
    ( MarkdownParseError(..)
    , MMark
    , parseMarkdown
    , markdownToHtml
    , MMark.render
    ) where
import Data.Text       (Text)
import Lucid
import Path            (File, Path, Rel)
import Text.MMark      (MMarkErr, MMark)
import Text.Megaparsec (ParseErrorBundle (..))
import qualified Path
import qualified Text.MMark as MMark
newtype MarkdownParseError = MarkdownParseError
    { MarkdownParseError -> ParseErrorBundle Text MMarkErr
unwrap :: ParseErrorBundle Text MMarkErr
    }
markdownToHtml
    :: Path Rel File 
    -> Text          
    -> Either MarkdownParseError (Html ())
markdownToHtml :: Path Rel File -> Text -> Either MarkdownParseError (Html ())
markdownToHtml Path Rel File
relFile Text
contents =
    MMark -> Html ()
MMark.render (MMark -> Html ())
-> Either MarkdownParseError MMark
-> Either MarkdownParseError (Html ())
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Path Rel File -> Text -> Either MarkdownParseError MMark
parseMarkdown Path Rel File
relFile Text
contents
parseMarkdown
    :: Path Rel File 
    -> Text          
    -> Either MarkdownParseError MMark
parseMarkdown :: Path Rel File -> Text -> Either MarkdownParseError MMark
parseMarkdown Path Rel File
relFile Text
contents =
    case FilePath -> Text -> Either (ParseErrorBundle Text MMarkErr) MMark
MMark.parse (Path Rel File -> FilePath
Path.fromRelFile Path Rel File
relFile) Text
contents of
        Left ParseErrorBundle Text MMarkErr
err -> MarkdownParseError -> Either MarkdownParseError MMark
forall a b. a -> Either a b
Left MarkdownParseError { unwrap :: ParseErrorBundle Text MMarkErr
unwrap = ParseErrorBundle Text MMarkErr
err }
        Right MMark
mmark -> MMark -> Either MarkdownParseError MMark
forall a b. b -> Either a b
Right MMark
mmark