aboutsummaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2009-01-31 18:30:26 +0000
committerfiddlosopher <fiddlosopher@788f1e2b-df1e-0410-8736-df70ead52e1b>2009-01-31 18:30:26 +0000
commitcdd3b67a055fa8dd6363317a62fdf18c7763b043 (patch)
tree1c1749fe76c7cf48dc2e9360cba5dedf2b40cb0b
parentede0d805a03f1f9a6c5c4790980a7de56eea8945 (diff)
downloadpandoc-cdd3b67a055fa8dd6363317a62fdf18c7763b043.tar.gz
Rewrote hsmarkdown in Haskell for portability.
For now, keeping the old shell script too. git-svn-id: https://pandoc.googlecode.com/svn/trunk@1533 788f1e2b-df1e-0410-8736-df70ead52e1b
-rw-r--r--pandoc.cabal14
-rw-r--r--src/hsmarkdown.hs44
2 files changed, 58 insertions, 0 deletions
diff --git a/pandoc.cabal b/pandoc.cabal
index a45072c12..a01461522 100644
--- a/pandoc.cabal
+++ b/pandoc.cabal
@@ -133,6 +133,9 @@ Flag highlighting
Flag executable
Description: Build the pandoc executable.
Default: True
+Flag wrappers
+ Description: Build the wrappers (hsmarkdown, html2markdown, markdown2pdf).
+ Default: True
Flag library
Description: Build the pandoc library.
Default: True
@@ -214,3 +217,14 @@ Executable pandoc
else
Buildable: False
+Executable hsmarkdown
+ Hs-Source-Dirs: src
+ Main-Is: hsmarkdown.hs
+ Ghc-Options: -Wall -threaded
+ Ghc-Prof-Options: -auto-all
+ Extensions: CPP, TemplateHaskell
+ if flag(wrappers)
+ Buildable: True
+ else
+ Buildable: False
+
diff --git a/src/hsmarkdown.hs b/src/hsmarkdown.hs
new file mode 100644
index 000000000..7f52083d9
--- /dev/null
+++ b/src/hsmarkdown.hs
@@ -0,0 +1,44 @@
+{-# LANGUAGE CPP #-}
+{-
+Copyright (C) 2006-8 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 : Main
+ Copyright : Copyright (C) 2006-8 John MacFarlane
+ License : GNU GPL, version 2 or above
+
+ Maintainer : John MacFarlane <jgm@berkeley@edu>
+ Stability : alpha
+ Portability : portable
+
+Wrapper around pandoc that emulates Markdown.pl as closely as possible.
+-}
+module Main where
+import System.Process
+import System.Environment ( getArgs )
+import Prelude hiding ( putStr, putStrLn, writeFile, readFile, getContents )
+import System.IO.UTF8
+import Control.Monad (forM_)
+
+main :: IO ()
+main = do
+ files <- getArgs
+ let runPandoc inp = readProcess "pandoc" ["--from", "markdown", "--to", "html", "--strict"] inp >>= putStrLn
+ if null files
+ then getContents >>= runPandoc
+ else forM_ files $ \f -> readFile f >>= runPandoc