EPUB Writer: Added explicit imports

This commit is contained in:
Matthew Pickering 2014-08-11 10:21:52 +01:00
parent 4e483dbf9a
commit 1f02ff60ba

View file

@ -29,7 +29,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
Conversion of 'Pandoc' documents to EPUB. Conversion of 'Pandoc' documents to EPUB.
-} -}
module Text.Pandoc.Writers.EPUB ( writeEPUB ) where module Text.Pandoc.Writers.EPUB ( writeEPUB ) where
import Data.IORef import Data.IORef ( IORef, newIORef, readIORef, modifyIORef )
import qualified Data.Map as M import qualified Data.Map as M
import Data.Maybe ( fromMaybe ) import Data.Maybe ( fromMaybe )
import Data.List ( isPrefixOf, isInfixOf, intercalate ) import Data.List ( isPrefixOf, isInfixOf, intercalate )
@ -40,27 +40,35 @@ import qualified Data.ByteString.Lazy as B
import qualified Data.ByteString.Lazy.Char8 as B8 import qualified Data.ByteString.Lazy.Char8 as B8
import qualified Text.Pandoc.UTF8 as UTF8 import qualified Text.Pandoc.UTF8 as UTF8
import Text.Pandoc.SelfContained ( makeSelfContained ) import Text.Pandoc.SelfContained ( makeSelfContained )
import Codec.Archive.Zip import Codec.Archive.Zip ( emptyArchive, addEntryToArchive, eRelativePath, fromEntry , Entry, toEntry, fromArchive)
import Control.Applicative ((<$>)) import Control.Applicative ((<$>))
import Data.Time.Clock.POSIX import Data.Time.Clock.POSIX ( getPOSIXTime )
import Data.Time import Data.Time (getCurrentTime,UTCTime, formatTime)
import System.Locale import System.Locale ( defaultTimeLocale )
import Text.Pandoc.Shared hiding ( Element ) import Text.Pandoc.Shared ( trimr, renderTags', safeRead, uniqueIdent, trim
import qualified Text.Pandoc.Shared as Shared , normalizeDate, readDataFile, stringify, warn
, hierarchicalize, fetchItem' )
import qualified Text.Pandoc.Shared as S (Element(..))
import Text.Pandoc.Builder (fromList, setMeta) import Text.Pandoc.Builder (fromList, setMeta)
import Text.Pandoc.Options import Text.Pandoc.Options ( WriterOptions(..)
, HTMLMathMethod(..)
, EPUBVersion(..)
, ObfuscationMethod(NoObfuscation) )
import Text.Pandoc.Definition import Text.Pandoc.Definition
import Text.Pandoc.Walk import Text.Pandoc.Walk (walk, walkM)
import Control.Monad.State import Control.Monad.State (modify, get, execState, State, put, evalState)
import Text.XML.Light hiding (ppTopElement) import Control.Monad (foldM, when, mplus, liftM)
import Text.Pandoc.UUID import Text.XML.Light ( unode, Element(..), unqual, Attr(..), add_attrs
import Text.Pandoc.Writers.HTML , strContent, lookupAttr, Node(..), QName(..), parseXML
, onlyElems, node, ppElement)
import Text.Pandoc.UUID (getRandomUUID)
import Text.Pandoc.Writers.HTML (writeHtmlString, writeHtml)
import Data.Char ( toLower, isDigit, isAlphaNum ) import Data.Char ( toLower, isDigit, isAlphaNum )
import Network.URI ( unEscapeString ) import Network.URI ( unEscapeString )
import Text.Pandoc.MIME (getMimeType) import Text.Pandoc.MIME (getMimeType)
import qualified Control.Exception as E import qualified Control.Exception as E
import Text.Blaze.Html.Renderer.Utf8 (renderHtml) import Text.Blaze.Html.Renderer.Utf8 (renderHtml)
import Text.HTML.TagSoup import Text.HTML.TagSoup (Tag(TagOpen), fromAttrib, parseTags)
-- A Chapter includes a list of blocks and maybe a section -- A Chapter includes a list of blocks and maybe a section
-- number offset. Note, some chapters are unnumbered. The section -- number offset. Note, some chapters are unnumbered. The section
@ -524,8 +532,8 @@ writeEPUB opts doc@(Pandoc meta _) = do
let tocLevel = writerTOCDepth opts let tocLevel = writerTOCDepth opts
let navPointNode :: (Int -> String -> String -> [Element] -> Element) let navPointNode :: (Int -> String -> String -> [Element] -> Element)
-> Shared.Element -> State Int Element -> S.Element -> State Int Element
navPointNode formatter (Sec _ nums (ident,_,_) ils children) = do navPointNode formatter (S.Sec _ nums (ident,_,_) ils children) = do
n <- get n <- get
modify (+1) modify (+1)
let showNums :: [Int] -> String let showNums :: [Int] -> String
@ -537,12 +545,12 @@ writeEPUB opts doc@(Pandoc meta _) = do
let src = case lookup ident reftable of let src = case lookup ident reftable of
Just x -> x Just x -> x
Nothing -> error (ident ++ " not found in reftable") Nothing -> error (ident ++ " not found in reftable")
let isSec (Sec lev _ _ _ _) = lev <= tocLevel let isSec (S.Sec lev _ _ _ _) = lev <= tocLevel
isSec _ = False isSec _ = False
let subsecs = filter isSec children let subsecs = filter isSec children
subs <- mapM (navPointNode formatter) subsecs subs <- mapM (navPointNode formatter) subsecs
return $ formatter n tit src subs return $ formatter n tit src subs
navPointNode _ (Blk _) = error "navPointNode encountered Blk" navPointNode _ (S.Blk _) = error "navPointNode encountered Blk"
let navMapFormatter :: Int -> String -> String -> [Element] -> Element let navMapFormatter :: Int -> String -> String -> [Element] -> Element
navMapFormatter n tit src subs = unode "navPoint" ! navMapFormatter n tit src subs = unode "navPoint" !