Put date in YYYY-MM-DD format if possible for HTML, docx metadata.

Added normalizeDate to Text.Pandoc.Shared.
This commit is contained in:
John MacFarlane 2012-01-28 15:54:05 -08:00
parent 98e5b61703
commit 3a0b3df007
8 changed files with 31 additions and 9 deletions

View file

@ -203,6 +203,8 @@ Library
zip-archive >= 0.1.1.7 && < 0.2, zip-archive >= 0.1.1.7 && < 0.2,
utf8-string >= 0.3 && < 0.4, utf8-string >= 0.3 && < 0.4,
old-time >= 1 && < 1.2, old-time >= 1 && < 1.2,
old-locale >= 1 && < 1.1,
time >= 1.2 && < 1.5,
HTTP >= 4000.0.5 && < 4000.3, HTTP >= 4000.0.5 && < 4000.3,
texmath >= 0.6 && < 0.7, texmath >= 0.6 && < 0.7,
xml >= 1.3.5 && < 1.4, xml >= 1.3.5 && < 1.4,
@ -294,6 +296,8 @@ Executable pandoc
zip-archive >= 0.1.1.7 && < 0.2, zip-archive >= 0.1.1.7 && < 0.2,
utf8-string >= 0.3 && < 0.4, utf8-string >= 0.3 && < 0.4,
old-time >= 1 && < 1.2, old-time >= 1 && < 1.2,
old-locale >= 1 && < 1.1,
time >= 1.2 && < 1.5,
HTTP >= 4000.0.5 && < 4000.3, HTTP >= 4000.0.5 && < 4000.3,
texmath >= 0.6 && < 0.7, texmath >= 0.6 && < 0.7,
xml >= 1.3.5 && < 1.4, xml >= 1.3.5 && < 1.4,

View file

@ -46,6 +46,8 @@ module Text.Pandoc.Shared (
toRomanNumeral, toRomanNumeral,
escapeURI, escapeURI,
tabFilter, tabFilter,
-- * Date/time
normalizeDate,
-- * Pandoc block and inline list processing -- * Pandoc block and inline list processing
orderedListMarkers, orderedListMarkers,
normalizeSpaces, normalizeSpaces,
@ -81,9 +83,12 @@ import System.Directory
import System.FilePath ( (</>) ) import System.FilePath ( (</>) )
import Data.Generics (Typeable, Data) import Data.Generics (Typeable, Data)
import qualified Control.Monad.State as S import qualified Control.Monad.State as S
import Control.Monad (msum)
import Paths_pandoc (getDataFileName) import Paths_pandoc (getDataFileName)
import Text.Pandoc.Highlighting (Style, pygments) import Text.Pandoc.Highlighting (Style, pygments)
import Text.Pandoc.Pretty (charWidth) import Text.Pandoc.Pretty (charWidth)
import System.Locale (defaultTimeLocale)
import Data.Time
-- --
-- List processing -- List processing
@ -217,6 +222,18 @@ tabFilter tabStop =
x : go (spsToNextStop - 1) xs x : go (spsToNextStop - 1) xs
in go tabStop in go tabStop
--
-- Date/time
--
-- | Parse a date and convert (if possible) to "YYYY-MM-DD" format.
normalizeDate :: String -> Maybe String
normalizeDate s = fmap (formatTime defaultTimeLocale "%F")
(msum $ map (\fs -> parsetimeWith fs s) formats :: Maybe Day)
where parsetimeWith = parseTime defaultTimeLocale
formats = ["%x","%m/%d/%Y", "%D","%F", "%d %b %Y",
"%d %B %Y", "%b. %d, %Y", "%B %d, %Y"]
-- --
-- Pandoc block and inline list processing -- Pandoc block and inline list processing
-- --

View file

@ -97,7 +97,7 @@ writeDocx :: Maybe FilePath -- ^ Path specified by --reference-docx
-> WriterOptions -- ^ Writer options -> WriterOptions -- ^ Writer options
-> Pandoc -- ^ Document to convert -> Pandoc -- ^ Document to convert
-> IO B.ByteString -> IO B.ByteString
writeDocx mbRefDocx opts doc@(Pandoc (Meta tit auths _) _) = do writeDocx mbRefDocx opts doc@(Pandoc (Meta tit auths date) _) = do
let datadir = writerUserDataDir opts let datadir = writerUserDataDir opts
refArchive <- liftM toArchive $ refArchive <- liftM toArchive $
case mbRefDocx of case mbRefDocx of
@ -161,7 +161,8 @@ writeDocx mbRefDocx opts doc@(Pandoc (Meta tit auths _) _) = do
,("xmlns:dcmitype","http://purl.org/dc/dcmitype/") ,("xmlns:dcmitype","http://purl.org/dc/dcmitype/")
,("xmlns:xsi","http://www.w3.org/2001/XMLSchema-instance")] ,("xmlns:xsi","http://www.w3.org/2001/XMLSchema-instance")]
$ mknode "dc:title" [] (stringify tit) $ mknode "dc:title" [] (stringify tit)
: mknode "dcterms:created" [("xsi:type","dcterms:W3CDTF")] () -- put doc date here : mknode "dcterms:created" [("xsi:type","dcterms:W3CDTF")]
(maybe "" id $ normalizeDate $ stringify date)
: mknode "dcterms:modified" [("xsi:type","dcterms:W3CDTF")] () -- put current time here : mknode "dcterms:modified" [("xsi:type","dcterms:W3CDTF")] () -- put current time here
: map (mknode "dc:creator" [] . stringify) auths : map (mknode "dc:creator" [] . stringify) auths
let docPropsEntry = toEntry docPropsPath epochtime $ fromString $ showTopElement' docProps let docPropsEntry = toEntry docPropsPath epochtime $ fromString $ showTopElement' docProps

View file

@ -182,13 +182,13 @@ inTemplate :: TemplateTarget a
inTemplate opts tit auths authsMeta date toc body' newvars = inTemplate opts tit auths authsMeta date toc body' newvars =
let title' = renderHtml tit let title' = renderHtml tit
date' = renderHtml date date' = renderHtml date
dateMeta = maybe [] (\x -> [("date-meta",x)]) $ normalizeDate date'
variables = writerVariables opts ++ newvars variables = writerVariables opts ++ newvars
context = variables ++ context = variables ++ dateMeta ++
[ ("body", dropWhile (=='\n') $ renderHtml body') [ ("body", dropWhile (=='\n') $ renderHtml body')
, ("pagetitle", stripTags title') , ("pagetitle", stripTags title')
, ("title", title') , ("title", title')
, ("date", date') , ("date", date')
, ("date-meta", stripTags date')
, ("idprefix", writerIdentifierPrefix opts) , ("idprefix", writerIdentifierPrefix opts)
, ("slidy-url", "http://www.w3.org/Talks/Tools/Slidy2") , ("slidy-url", "http://www.w3.org/Talks/Tools/Slidy2")
, ("s5-url", "s5/default") ] ++ , ("s5-url", "s5/default") ] ++

View file

@ -6,7 +6,7 @@
<meta name="generator" content="pandoc" /> <meta name="generator" content="pandoc" />
<meta name="author" content="Sam Smith" /> <meta name="author" content="Sam Smith" />
<meta name="author" content="Jen Jones" /> <meta name="author" content="Jen Jones" />
<meta name="date" content="July 15, 2006" /> <meta name="date" content="2006-07-15" />
<title>My S5 Document</title> <title>My S5 Document</title>
<!-- configuration parameters --> <!-- configuration parameters -->
<meta name="defaultView" content="slideshow" /> <meta name="defaultView" content="slideshow" />

View file

@ -6,7 +6,7 @@
<meta name="generator" content="pandoc" /> <meta name="generator" content="pandoc" />
<meta name="author" content="Sam Smith" /> <meta name="author" content="Sam Smith" />
<meta name="author" content="Jen Jones" /> <meta name="author" content="Jen Jones" />
<meta name="date" content="July 15, 2006" /> <meta name="date" content="2006-07-15" />
<title>My S5 Document</title> <title>My S5 Document</title>
<!-- configuration parameters --> <!-- configuration parameters -->
<meta name="defaultView" content="slideshow" /> <meta name="defaultView" content="slideshow" />

View file

@ -6,7 +6,7 @@
<meta name="generator" content="pandoc" /> <meta name="generator" content="pandoc" />
<meta name="author" content="Sam Smith" /> <meta name="author" content="Sam Smith" />
<meta name="author" content="Jen Jones" /> <meta name="author" content="Jen Jones" />
<meta name="date" content="July 15, 2006" /> <meta name="date" content="2006-07-15" />
<title>My S5 Document</title> <title>My S5 Document</title>
<link rel="stylesheet" href="main.css" type="text/css" /> <link rel="stylesheet" href="main.css" type="text/css" />
STUFF INSERTED STUFF INSERTED

View file

@ -6,7 +6,7 @@
<meta name="generator" content="pandoc" /> <meta name="generator" content="pandoc" />
<meta name="author" content="John MacFarlane" /> <meta name="author" content="John MacFarlane" />
<meta name="author" content="Anonymous" /> <meta name="author" content="Anonymous" />
<meta name="date" content="July 17, 2006" /> <meta name="date" content="2006-07-17" />
<title>Pandoc Test Suite</title> <title>Pandoc Test Suite</title>
</head> </head>
<body> <body>