Minor ghc 8.8 fixups.
This commit is contained in:
parent
20c87962e3
commit
7caaa3d5d6
3 changed files with 8 additions and 5 deletions
|
@ -127,7 +127,6 @@ import System.FilePath
|
|||
import qualified System.FilePath.Glob as IO (glob)
|
||||
import qualified System.FilePath.Posix as Posix
|
||||
import qualified System.Directory as IO (getModificationTime)
|
||||
import Control.Monad as M (fail)
|
||||
import Control.Monad.State.Strict
|
||||
import Control.Monad.Except
|
||||
import Data.Word (Word8)
|
||||
|
@ -990,7 +989,8 @@ instance PandocMonad PandocPure where
|
|||
u : us -> do
|
||||
modifyPureState $ \st -> st { stUniqStore = us }
|
||||
return u
|
||||
_ -> M.fail "uniq store ran out of elements"
|
||||
_ -> throwError $ PandocShouldNeverHappenError
|
||||
"uniq store ran out of elements"
|
||||
openURL u = throwError $ PandocResourceNotFound u
|
||||
readFileLazy fp = do
|
||||
fps <- getsPureState stFiles
|
||||
|
|
|
@ -117,7 +117,10 @@ docHToInlines isCode d' =
|
|||
$ map B.code $ splitBy (=='\n') s
|
||||
| otherwise -> B.text s
|
||||
DocParagraph _ -> mempty
|
||||
DocIdentifier (_,s,_) -> B.codeWith ("",["haskell","identifier"],[]) s
|
||||
DocIdentifier ident ->
|
||||
case toRegular (DocIdentifier ident) of
|
||||
DocIdentifier s -> B.codeWith ("",["haskell","identifier"],[]) s
|
||||
_ -> mempty
|
||||
DocIdentifierUnchecked s -> B.codeWith ("",["haskell","identifier"],[]) s
|
||||
DocModule s -> B.codeWith ("",["haskell","module"],[]) s
|
||||
DocWarning _ -> mempty -- TODO
|
||||
|
@ -133,7 +136,8 @@ docHToInlines isCode d' =
|
|||
DocDefList _ -> mempty
|
||||
DocCodeBlock _ -> mempty
|
||||
DocHyperlink h -> B.link (hyperlinkUrl h) (hyperlinkUrl h)
|
||||
(maybe (B.text $ hyperlinkUrl h) B.text $ hyperlinkLabel h)
|
||||
(maybe (B.text $ hyperlinkUrl h) (docHToInlines isCode)
|
||||
(hyperlinkLabel h))
|
||||
DocPic p -> B.image (pictureUri p) (fromMaybe (pictureUri p) $ pictureTitle p)
|
||||
(maybe mempty B.text $ pictureTitle p)
|
||||
DocAName s -> B.spanWith (s,["anchor"],[]) mempty
|
||||
|
|
|
@ -11,7 +11,6 @@ import Text.Pandoc
|
|||
import Text.Pandoc.Arbitrary ()
|
||||
import Text.Pandoc.Builder
|
||||
import Text.Pandoc.Writers.RST
|
||||
import Text.Pandoc.Templates (compileTemplate)
|
||||
import qualified Data.Text as T
|
||||
|
||||
infix 4 =:
|
||||
|
|
Loading…
Add table
Reference in a new issue