Don't use OverloadedStrings in ODT writer.
Remove version dependency from bytestring. git-svn-id: https://pandoc.googlecode.com/svn/trunk@1359 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
parent
31e261ca39
commit
7b986acd72
2 changed files with 4 additions and 9 deletions
|
@ -1,4 +1,4 @@
|
||||||
{-# LANGUAGE TemplateHaskell, OverloadedStrings #-}
|
{-# LANGUAGE TemplateHaskell #-}
|
||||||
{-
|
{-
|
||||||
Copyright (C) 2008 John MacFarlane <jgm@berkeley.edu>
|
Copyright (C) 2008 John MacFarlane <jgm@berkeley.edu>
|
||||||
|
|
||||||
|
@ -43,11 +43,7 @@ import Text.XML.Light
|
||||||
import Text.XML.Light.Cursor
|
import Text.XML.Light.Cursor
|
||||||
import Text.Pandoc.Shared ( withTempDir )
|
import Text.Pandoc.Shared ( withTempDir )
|
||||||
import Network.URI ( isURI )
|
import Network.URI ( isURI )
|
||||||
import Data.String ( IsString (..) )
|
import qualified Data.ByteString.Char8 as B ( writeFile, pack )
|
||||||
import qualified Data.ByteString.Char8 as B ( writeFile, pack, ByteString )
|
|
||||||
|
|
||||||
instance IsString B.ByteString
|
|
||||||
where fromString = B.pack
|
|
||||||
|
|
||||||
-- | Produce an ODT file from OpenDocument XML.
|
-- | Produce an ODT file from OpenDocument XML.
|
||||||
saveOpenDocumentAsODT :: FilePath -- ^ Pathname of ODT file to be produced.
|
saveOpenDocumentAsODT :: FilePath -- ^ Pathname of ODT file to be produced.
|
||||||
|
@ -68,7 +64,7 @@ saveOpenDocumentAsODT destinationODTPath sourceDirRelative xml = do
|
||||||
withTempDir "pandoc-odt" $ \tempDir -> do
|
withTempDir "pandoc-odt" $ \tempDir -> do
|
||||||
let tempODT = tempDir </> "reference.odt"
|
let tempODT = tempDir </> "reference.odt"
|
||||||
copyFile "odt-styles/reference.odt" tempODT
|
copyFile "odt-styles/reference.odt" tempODT
|
||||||
B.writeFile tempODT $(contentsOf "odt-styles/reference.odt")
|
B.writeFile tempODT $ B.pack $(contentsOf "odt-styles/reference.odt")
|
||||||
createDirectory $ tempDir </> "Pictures"
|
createDirectory $ tempDir </> "Pictures"
|
||||||
xml' <- handlePictures tempODT sourceDirRelative xml
|
xml' <- handlePictures tempODT sourceDirRelative xml
|
||||||
writeFile (tempDir </> "content.xml") xml'
|
writeFile (tempDir </> "content.xml") xml'
|
||||||
|
|
|
@ -74,8 +74,7 @@ Library
|
||||||
Build-depends: highlighting-kate
|
Build-depends: highlighting-kate
|
||||||
cpp-options: -DHIGHLIGHTING
|
cpp-options: -DHIGHLIGHTING
|
||||||
Build-Depends: parsec < 3, xhtml, mtl, network, filepath, process, directory, utf8-string,
|
Build-Depends: parsec < 3, xhtml, mtl, network, filepath, process, directory, utf8-string,
|
||||||
template-haskell, bytestring == 0.9.0.1
|
template-haskell, bytestring
|
||||||
-- Note: bytestring-0.9.1.0 contains an InString instance for ByteString
|
|
||||||
Hs-Source-Dirs: .
|
Hs-Source-Dirs: .
|
||||||
Exposed-Modules: Text.Pandoc,
|
Exposed-Modules: Text.Pandoc,
|
||||||
Text.Pandoc.Blocks,
|
Text.Pandoc.Blocks,
|
||||||
|
|
Loading…
Reference in a new issue