Use CPP to simplify build procedure for Highlighting.hs module.
This is no longer built by Setup.hs in the pre-configure phase. git-svn-id: https://pandoc.googlecode.com/svn/trunk@1339 788f1e2b-df1e-0410-8736-df70ead52e1b
This commit is contained in:
parent
57df7f5eb6
commit
2751608d9b
4 changed files with 15 additions and 53 deletions
9
Setup.hs
9
Setup.hs
|
@ -22,14 +22,6 @@ myPostConf _ configFlags pkgDescription buildInfo = do
|
|||
fillAsciiMathMLTemplate
|
||||
fillS5WriterTemplate
|
||||
fillDefaultHeadersTemplate
|
||||
let deps = packageDeps buildInfo
|
||||
let highlighting = any (\id -> pkgName id == "highlighting-kate") deps
|
||||
let highlightingModule = if highlighting
|
||||
then combine "templates" "Highlighting.yes.hs"
|
||||
else combine "templates" "Highlighting.no.hs"
|
||||
copyFile highlightingModule $ joinPath ["Text", "Pandoc", "Highlighting.hs"]
|
||||
putStrLn $ " Text/Pandoc/Highlighting.hs [" ++
|
||||
(if highlighting then "with" else "without") ++ " syntax highlighting support]"
|
||||
|
||||
-- Fill templateFile with data in dataFiles and write to outputFile.
|
||||
fillTemplate :: [FilePath] -> FilePath -> FilePath -> IO ()
|
||||
|
@ -61,7 +53,6 @@ myPostClean _ _ _ _ = do
|
|||
putStrLn "Removing source files generated from templates:"
|
||||
removeGeneratedFile $ joinPath [pandocPath, "ASCIIMathML.hs"]
|
||||
removeGeneratedFile $ joinPath [pandocPath, "DefaultHeaders.hs"]
|
||||
removeGeneratedFile $ joinPath [pandocPath, "Highlighting.hs"]
|
||||
removeGeneratedFile $ joinPath [pandocPath, "Writers", "S5.hs"]
|
||||
|
||||
-- Remove file and print message.
|
||||
|
|
|
@ -1,3 +1,4 @@
|
|||
{-# LANGUAGE CPP #-}
|
||||
{-
|
||||
Copyright (C) 2008 John MacFarlane <jgm@berkeley.edu>
|
||||
|
||||
|
@ -29,12 +30,13 @@ Exports functions for syntax highlighting.
|
|||
-}
|
||||
|
||||
module Text.Pandoc.Highlighting ( languages, highlightHtml, defaultHighlightingCss ) where
|
||||
import Text.Highlighting.Kate ( languages, highlightAs, formatAsXHtml, FormatOption (..), defaultHighlightingCss )
|
||||
import Text.XHtml
|
||||
import Text.Pandoc.Definition
|
||||
#ifdef HIGHLIGHTING
|
||||
import Text.Highlighting.Kate ( languages, highlightAs, formatAsXHtml, FormatOption (..), defaultHighlightingCss )
|
||||
import Data.List (find, lookup)
|
||||
import Data.Maybe (fromMaybe)
|
||||
import Data.Char (toLower)
|
||||
import Text.Pandoc.Definition
|
||||
|
||||
highlightHtml :: Attr -> String -> Either String Html
|
||||
highlightHtml (_, classes, keyvals) rawCode =
|
||||
|
@ -50,3 +52,13 @@ highlightHtml (_, classes, keyvals) rawCode =
|
|||
Left err -> Left err
|
||||
Right hl -> Right $ formatAsXHtml fmtOpts lang hl
|
||||
|
||||
#else
|
||||
defaultHighlightingCss :: String
|
||||
defaultHighlightingCss = ""
|
||||
|
||||
languages :: [String]
|
||||
languages = []
|
||||
|
||||
highlightHtml :: Attr -> String -> Either String Html
|
||||
highlightHtml _ _ = Left "Pandoc was not compiled with support for highlighting"
|
||||
#endif
|
|
@ -47,6 +47,7 @@ Library
|
|||
Build-Depends: base < 3
|
||||
if flag(highlighting)
|
||||
Build-depends: highlighting-kate
|
||||
cpp-options: -DHIGHLIGHTING
|
||||
Build-Depends: parsec < 3, xhtml, mtl, network, filepath
|
||||
Hs-Source-Dirs: .
|
||||
Exposed-Modules: Text.Pandoc,
|
||||
|
|
|
@ -1,42 +0,0 @@
|
|||
{-
|
||||
Copyright (C) 2008 John MacFarlane <jgm@berkeley.edu>
|
||||
|
||||
This program is free software; you can redistribute it and/or modify
|
||||
it under the terms of the GNU General Public License as published by
|
||||
the Free Software Foundation; either version 2 of the License, or
|
||||
(at your option) any later version.
|
||||
|
||||
This program is distributed in the hope that it will be useful,
|
||||
but WITHOUT ANY WARRANTY; without even the implied warranty of
|
||||
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the
|
||||
GNU General Public License for more details.
|
||||
|
||||
You should have received a copy of the GNU General Public License
|
||||
along with this program; if not, write to the Free Software
|
||||
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA 02111-1307 USA
|
||||
-}
|
||||
|
||||
{- |
|
||||
Module : Text.Pandoc.Highlighting
|
||||
Copyright : Copyright (C) 2008 John MacFarlane
|
||||
License : GNU GPL, version 2 or above
|
||||
|
||||
Maintainer : John MacFarlane <jgm@berkeley.edu>
|
||||
Stability : alpha
|
||||
Portability : portable
|
||||
|
||||
Exports functions for syntax highlighting.
|
||||
-}
|
||||
|
||||
module Text.Pandoc.Highlighting ( languages, highlightHtml, defaultHighlightingCss ) where
|
||||
import Text.XHtml
|
||||
import Text.Pandoc.Definition
|
||||
|
||||
defaultHighlightingCss :: String
|
||||
defaultHighlightingCss = ""
|
||||
|
||||
languages :: [String]
|
||||
languages = []
|
||||
|
||||
highlightHtml :: Attr -> String -> Either String Html
|
||||
highlightHtml _ _ = Left "Pandoc was not compiled with support for highlighting"
|
Loading…
Reference in a new issue