aboutsummaryrefslogtreecommitdiff
path: root/src/Text/Pandoc/Writers/JATS/References.hs
blob: 5b19fd03415ec6ff686964a4aaee5756ac0489bc (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
{-# LANGUAGE LambdaCase        #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
   Module      : Text.Pandoc.Writers.JATS.References
   Copyright   : © 2021 Albert Krewinkel
   License     : GNU GPL, version 2 or above

   Maintainer  : Albert Krewinkel <tarleb@zeitkraut.de>
   Stability   : alpha
   Portability : portable

Creation of a bibliography list using @<element-citation>@ elements in
reference items.
-}
module Text.Pandoc.Writers.JATS.References
  ( referencesToJATS
  , referenceToJATS
  ) where

import Citeproc.Pandoc ()
import Citeproc.Types
  ( Date (..), DateParts (..), ItemId (..), Name (..), Reference (..)
  , Val (..) , lookupVariable, valToText
  )
import Data.Text (Text)
import Text.DocLayout (Doc, empty, isEmpty, literal, vcat)
import Text.Pandoc.Class.PandocMonad (PandocMonad)
import Text.Pandoc.Builder (Inlines)
import Text.Pandoc.Options (WriterOptions)
import Text.Pandoc.Shared (tshow)
import Text.Pandoc.Writers.JATS.Types
import Text.Pandoc.XML (escapeNCName, escapeStringForXML, inTags)
import qualified Data.Text as T

referencesToJATS :: PandocMonad m
                 => WriterOptions
                 -> [Reference Inlines]
                 -> JATS m (Doc Text)
referencesToJATS opts =
  fmap (inTags True "ref-list" [] . vcat) . mapM (referenceToJATS opts)

referenceToJATS :: PandocMonad m
                => WriterOptions
                -> Reference Inlines
                -> JATS m (Doc Text)
referenceToJATS _opts ref = do
  let refType = referenceType ref
  let pubType = [("publication-type", refType) | not (T.null refType)]
  let ident = escapeNCName $ "ref-" <> unItemId (referenceId ref)
  let wrap = inTags True "ref" [("id", ident)]
           . inTags True "element-citation" pubType
  return . wrap . vcat $
    [ authors
    , "title" `varInTag`
      if refType == "book"
      then "source"
      else "article-title"
    , if refType == "book"
      then empty
      else "container-title" `varInTag` "source"
    , editors
    , "publisher"       `varInTag` "publisher-name"
    , "publisher-place" `varInTag` "publisher-loc"
    , yearTag
    , accessed
    , "volume"          `varInTag` "volume"
    , "issue"           `varInTag` "issue"
    , "page-first"      `varInTag` "fpage"
    , "page-last"       `varInTag` "lpage"
    , "pages"           `varInTag` "page-range"
    , "ISBN"            `varInTag` "isbn"
    , "ISSN"            `varInTag` "issn"
    , varInTagWith "doi"  "pub-id" [("pub-id-type", "doi")]
    , varInTagWith "pmid" "pub-id" [("pub-id-type", "pmid")]
    ]
  where
    varInTag var tagName = varInTagWith var tagName []

    varInTagWith var tagName tagAttribs =
      case lookupVariable var ref >>= valToText of
        Nothing  -> mempty
        Just val -> inTags' tagName tagAttribs . literal $
                    escapeStringForXML val

    authors = case lookupVariable "author" ref of
      Just (NamesVal names) ->
        inTags True "person-group" [("person-group-type", "author")] . vcat $
        map toNameElements names
      _                     -> empty

    editors = case lookupVariable "editor" ref of
      Just (NamesVal names) ->
        inTags True "person-group" [("person-group-type", "editor")] . vcat $
        map toNameElements names
      _                     -> empty

    yearTag =
      case lookupVariable "issued" ref of
        Just (DateVal date) -> toDateElements date
        _ -> empty

    accessed =
      case lookupVariable "accessed" ref of
        Just (DateVal d) -> inTags' "date-in-citation"
                                    [("content-type", "access-date")]
                                    (toDateElements d)
        _ -> empty

toDateElements :: Date -> Doc Text
toDateElements date =
  case dateParts date of
    dp@(DateParts (y:m:d:_)):_ -> yearElement y dp <>
                                  monthElement m <>
                                  dayElement d
    dp@(DateParts (y:m:_)):_   -> yearElement y dp <> monthElement m
    dp@(DateParts (y:_)):_     -> yearElement y dp
    _                          -> empty

yearElement :: Int -> DateParts -> Doc Text
yearElement year dp =
  inTags' "year" [("iso-8601-date", iso8601 dp)] $ literal (fourDigits year)

monthElement :: Int -> Doc Text
monthElement month = inTags' "month" [] . literal $ twoDigits month

dayElement :: Int -> Doc Text
dayElement day = inTags' "day" [] . literal $ twoDigits day

iso8601 :: DateParts -> Text
iso8601 = T.intercalate "-" . \case
  DateParts (y:m:d:_) -> [fourDigits y, twoDigits m, twoDigits d]
  DateParts (y:m:_)   -> [fourDigits y, twoDigits m]
  DateParts (y:_)     -> [fourDigits y]
  _                   -> []

twoDigits :: Int -> Text
twoDigits n = T.takeEnd 2 $ '0' `T.cons` tshow n

fourDigits :: Int -> Text
fourDigits n = T.takeEnd 4 $ "000" <> tshow n

toNameElements :: Name -> Doc Text
toNameElements name =
  if not (isEmpty nameTags)
  then inTags' "name" [] nameTags
  else nameLiteral name `inNameTag` "string-name"
    where
      inNameTag mVal tag = case mVal of
        Nothing  -> empty
        Just val -> inTags' tag [] . literal $ escapeStringForXML val
      surnamePrefix = maybe mempty (`T.snoc` ' ') $
                      nameNonDroppingParticle name
      givenSuffix = maybe mempty (T.cons ' ') $
                    nameDroppingParticle name
      nameTags = mconcat
        [ ((surnamePrefix <>) <$> nameFamily name) `inNameTag` "surname"
        , ((<> givenSuffix) <$> nameGiven name) `inNameTag` "given-names"
        , nameSuffix name `inNameTag` "suffix"
        ]

-- | Put the supplied contents between start and end tags of tagType,
--   with specified attributes.
inTags' :: Text -> [(Text, Text)] -> Doc Text -> Doc Text
inTags' = inTags False