aboutsummaryrefslogtreecommitdiff
path: root/data
diff options
context:
space:
mode:
Diffstat (limited to 'data')
-rw-r--r--data/bash_completion.tpl12
-rw-r--r--data/creole.lua190
-rw-r--r--data/pandoc.List.lua142
-rw-r--r--data/pandoc.lua1169
-rw-r--r--data/pptx/ppt/slideMasters/slideMaster1.xml2
-rw-r--r--data/sample.lua20
-rw-r--r--data/templates/affiliations.jats44
-rw-r--r--data/templates/article.jats_publishing17
-rw-r--r--data/templates/default.jats_articleauthoring12
-rw-r--r--data/templates/default.latex39
-rw-r--r--data/templates/default.markua21
-rw-r--r--data/templates/default.revealjs5
-rw-r--r--data/templates/default.rtf2
13 files changed, 294 insertions, 1381 deletions
diff --git a/data/bash_completion.tpl b/data/bash_completion.tpl
index d065c34bb..440abc3e6 100644
--- a/data/bash_completion.tpl
+++ b/data/bash_completion.tpl
@@ -4,7 +4,7 @@
_pandoc()
{
- local cur prev opts lastc informats outformats datafiles
+ local cur prev opts lastc informats outformats highlight_styles datafiles
COMPREPLY=()
cur="${COMP_WORDS[COMP_CWORD]}"
prev="${COMP_WORDS[COMP_CWORD-1]}"
@@ -57,10 +57,18 @@ _pandoc()
COMPREPLY=( $(compgen -W "section chapter part" -- ${cur}) )
return 0
;;
- --highlight-style)
+ --highlight-style|--print-highlight-style)
COMPREPLY=( $(compgen -W "${highlight_styles}" -- ${cur}) )
return 0
;;
+ --eol)
+ COMPREPLY=( $(compgen -W "crlf lf native" -- ${cur}) )
+ return 0
+ ;;
+ --markdown-headings)
+ COMPREPLY=( $(compgen -W "setext atx" -- ${cur}) )
+ return 0
+ ;;
*)
;;
esac
diff --git a/data/creole.lua b/data/creole.lua
new file mode 100644
index 000000000..590dfc871
--- /dev/null
+++ b/data/creole.lua
@@ -0,0 +1,190 @@
+-- A sample custom reader for Creole 1.0 (common wiki markup)
+-- http://www.wikicreole.org/wiki/CheatSheet
+
+-- For better performance we put these functions in local variables:
+local P, S, R, Cf, Cc, Ct, V, Cs, Cg, Cb, B, C, Cmt =
+ lpeg.P, lpeg.S, lpeg.R, lpeg.Cf, lpeg.Cc, lpeg.Ct, lpeg.V,
+ lpeg.Cs, lpeg.Cg, lpeg.Cb, lpeg.B, lpeg.C, lpeg.Cmt
+
+local whitespacechar = S(" \t\r\n")
+local specialchar = S("/*~[]\\{}|")
+local wordchar = (1 - (whitespacechar + specialchar))
+local spacechar = S(" \t")
+local newline = P"\r"^-1 * P"\n"
+local blankline = spacechar^0 * newline
+local endline = newline * #-blankline
+local endequals = spacechar^0 * P"="^0 * spacechar^0 * newline
+local cellsep = spacechar^0 * P"|"
+
+local function trim(s)
+ return (s:gsub("^%s*(.-)%s*$", "%1"))
+end
+
+local function ListItem(lev, ch)
+ local start
+ if ch == nil then
+ start = S"*#"
+ else
+ start = P(ch)
+ end
+ local subitem = function(c)
+ if lev < 6 then
+ return ListItem(lev + 1, c)
+ else
+ return (1 - 1) -- fails
+ end
+ end
+ local parser = spacechar^0
+ * start^lev
+ * #(- start)
+ * spacechar^0
+ * Ct((V"Inline" - (newline * spacechar^0 * S"*#"))^0)
+ * newline
+ * (Ct(subitem("*")^1) / pandoc.BulletList
+ +
+ Ct(subitem("#")^1) / pandoc.OrderedList
+ +
+ Cc(nil))
+ / function (ils, sublist)
+ return { pandoc.Plain(ils), sublist }
+ end
+ return parser
+end
+
+-- Grammar
+G = P{ "Doc",
+ Doc = Ct(V"Block"^0)
+ / pandoc.Pandoc ;
+ Block = blankline^0
+ * ( V"Header"
+ + V"HorizontalRule"
+ + V"CodeBlock"
+ + V"List"
+ + V"Table"
+ + V"Para") ;
+ Para = Ct(V"Inline"^1)
+ * newline
+ / pandoc.Para ;
+ HorizontalRule = spacechar^0
+ * P"----"
+ * spacechar^0
+ * newline
+ / pandoc.HorizontalRule;
+ Header = (P("=")^1 / string.len)
+ * spacechar^1
+ * Ct((V"Inline" - endequals)^1)
+ * endequals
+ / pandoc.Header;
+ CodeBlock = P"{{{"
+ * blankline
+ * C((1 - (newline * P"}}}"))^0)
+ * newline
+ * P"}}}"
+ / pandoc.CodeBlock;
+ Placeholder = P"<<<"
+ * C(P(1) - P">>>")^0
+ * P">>>"
+ / function() return pandoc.Div({}) end;
+ List = V"BulletList"
+ + V"OrderedList" ;
+ BulletList = Ct(ListItem(1,'*')^1)
+ / pandoc.BulletList ;
+ OrderedList = Ct(ListItem(1,'#')^1)
+ / pandoc.OrderedList ;
+ Table = (V"TableHeader" + Cc{})
+ * Ct(V"TableRow"^1)
+ / function(headrow, bodyrows)
+ local numcolumns = #(bodyrows[1])
+ local aligns = {}
+ local widths = {}
+ for i = 1,numcolumns do
+ aligns[i] = pandoc.AlignDefault
+ widths[i] = 0
+ end
+ return pandoc.utils.from_simple_table(
+ pandoc.SimpleTable({}, aligns, widths, headrow, bodyrows))
+ end ;
+ TableHeader = Ct(V"HeaderCell"^1)
+ * cellsep^-1
+ * spacechar^0
+ * newline ;
+ TableRow = Ct(V"BodyCell"^1)
+ * cellsep^-1
+ * spacechar^0
+ * newline ;
+ HeaderCell = cellsep
+ * P"="
+ * spacechar^0
+ * Ct((V"Inline" - (newline + cellsep))^0)
+ / function(ils) return { pandoc.Plain(ils) } end ;
+ BodyCell = cellsep
+ * spacechar^0
+ * Ct((V"Inline" - (newline + cellsep))^0)
+ / function(ils) return { pandoc.Plain(ils) } end ;
+ Inline = V"Emph"
+ + V"Strong"
+ + V"LineBreak"
+ + V"Link"
+ + V"URL"
+ + V"Image"
+ + V"Str"
+ + V"Space"
+ + V"SoftBreak"
+ + V"Escaped"
+ + V"Placeholder"
+ + V"Code"
+ + V"Special" ;
+ Str = wordchar^1
+ / pandoc.Str;
+ Escaped = P"~"
+ * C(P(1))
+ / pandoc.Str ;
+ Special = specialchar
+ / pandoc.Str;
+ Space = spacechar^1
+ / pandoc.Space ;
+ SoftBreak = endline
+ * # -(V"HorizontalRule" + V"CodeBlock")
+ / pandoc.SoftBreak ;
+ LineBreak = P"\\\\"
+ / pandoc.LineBreak ;
+ Code = P"{{{"
+ * C((1 - P"}}}")^0)
+ * P"}}}"
+ / trim / pandoc.Code ;
+ Link = P"[["
+ * C((1 - (P"]]" + P"|"))^0)
+ * (P"|" * Ct((V"Inline" - P"]]")^1))^-1 * P"]]"
+ / function(url, desc)
+ local txt = desc or {pandoc.Str(url)}
+ return pandoc.Link(txt, url)
+ end ;
+ Image = P"{{"
+ * #-P"{"
+ * C((1 - (S"}"))^0)
+ * (P"|" * Ct((V"Inline" - P"}}")^1))^-1
+ * P"}}"
+ / function(url, desc)
+ local txt = desc or ""
+ return pandoc.Image(txt, url)
+ end ;
+ URL = P"http"
+ * P"s"^-1
+ * P":"
+ * (1 - (whitespacechar + (S",.?!:;\"'" * #whitespacechar)))^1
+ / function(url)
+ return pandoc.Link(pandoc.Str(url), url)
+ end ;
+ Emph = P"//"
+ * Ct((V"Inline" - P"//")^1)
+ * P"//"
+ / pandoc.Emph ;
+ Strong = P"**"
+ * Ct((V"Inline" -P"**")^1)
+ * P"**"
+ / pandoc.Strong ;
+}
+
+function Reader(input, reader_options)
+ return lpeg.match(G, tostring(input))
+end
diff --git a/data/pandoc.List.lua b/data/pandoc.List.lua
deleted file mode 100644
index b33c30876..000000000
--- a/data/pandoc.List.lua
+++ /dev/null
@@ -1,142 +0,0 @@
---[[
-List.lua
-
-Copyright © 2017–2020 Albert Krewinkel
-
-Permission to use, copy, modify, and/or distribute this software for any
-purpose with or without fee is hereby granted, provided that the above
-copyright notice and this permission notice appear in all copies.
-
-THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES
-WITH REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF
-MERCHANTABILITY AND FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR
-ANY SPECIAL, DIRECT, INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES
-WHATSOEVER RESULTING FROM LOSS OF USE, DATA OR PROFITS, WHETHER IN AN
-ACTION OF CONTRACT, NEGLIGENCE OR OTHER TORTIOUS ACTION, ARISING OUT OF
-OR IN CONNECTION WITH THE USE OR PERFORMANCE OF THIS SOFTWARE. ]]
-
---- Pandoc's List type and helper methods
--- @classmod pandoc.List
--- @author Albert Krewinkel
--- @copyright © 2017–2020 Albert Krewinkel
--- @license MIT
-local List = {
- _VERSION = "1.0.0"
-}
-
---- Create a new list.
--- @param[opt] o table that should be altered into a list (default: `{}`)
--- @return the altered input table
-function List:new (o)
- o = o or {}
- setmetatable(o, self)
- self.__index = self
- return o
-end
-
---- Concatenates two lists.
--- @param list second list concatenated to the first
--- @return a new list containing all elements from list1 and list2
-function List:__concat (list)
- local res = List.clone(self)
- List.extend(res, list)
- return res
-end
-
---- Returns a (shallow) copy of the list.
-function List:clone ()
- local lst = setmetatable({}, getmetatable(self))
- List.extend(lst, self)
- return lst
-end
-
---- Adds the given list to the end of this list.
--- @param list list to appended
-function List:extend (list)
- for i = 1, #list do
- self[#self + 1] = list[i]
- end
-end
-
---- Returns a new list containing all items satisfying a given condition.
--- @param pred condition items must satisfy.
--- @return a new list containing all items for which `test` was true.
-function List:filter (pred)
- local res = setmetatable({}, getmetatable(self))
- for i = 1, #self do
- if pred(self[i], i) then
- res[#res + 1] = self[i]
- end
- end
- return res
-end
-
---- Returns the value and index of the first occurrence of the given item.
--- @param needle item to search for
--- @param[opt] init index at which the search is started (default: 1)
--- @return first item equal to the needle, or nil if no such item exists.
--- @return index of that element
-function List:find (needle, init)
- return List.find_if(self, function(x) return x == needle end, init)
-end
-
---- Returns the value and index of the first element for which the predicate
---- holds true.
--- @param pred the predicate function
--- @param[opt] init index at which the search is started (default: 1)
--- @return first item for which `test` succeeds, or nil if no such item exists.
--- @return index of that element
-function List:find_if (pred, init)
- init = (init == nil and 1) or (init < 0 and #self - init) or init
- for i = init, #self do
- if pred(self[i], i) then
- return self[i], i
- end
- end
- return nil
-end
-
---- Checks if the list has an item equal to the given needle.
--- @param needle item to search for
--- @param[opt] init index at which the search is started; defaults to 1.
--- @return true if a list item is equal to the needle, false otherwise
-function List:includes (needle, init)
- return not (List.find(self, needle, init) == nil)
-end
-
---- Insert an element into the list. Alias for `table.insert`.
--- @param list list
--- @param[opt] pos position at which the new element is to be inserted
--- @param value value to insert
-List.insert = table.insert
-
---- Returns a copy of the current list by applying the given function to
--- all elements.
--- @param fn function which is applied to all list items.
-function List:map (fn)
- local res = setmetatable({}, getmetatable(self))
- for i = 1, #self do
- res[i] = fn(self[i], i)
- end
- return res
-end
-
---- Remove element from list (alias for `table.remove`)
--- @param list list
--- @param[opt] pos position of the element to be removed (default: #list)
--- @return the removed element
-List.remove = table.remove
-
---- Sort list in-place (alias for `table.sort`)
--- @param list list
--- @param[opt] comp comparison function; default to `<` operator.
-List.sort = table.sort
-
--- Set metatable with __call metamethod. This allows the use of `List`
--- as a constructor function.
-local ListMT = {
- __call = List.new
-}
-setmetatable(List, ListMT)
-
-return List
diff --git a/data/pandoc.lua b/data/pandoc.lua
deleted file mode 100644
index 35ca20a84..000000000
--- a/data/pandoc.lua
+++ /dev/null
@@ -1,1169 +0,0 @@
---[[
-pandoc.lua
-
-Copyright © 2017–2019 Albert Krewinkel
-
-Permission to use, copy, modify, and/or distribute this software for any purpose
-with or without fee is hereby granted, provided that the above copyright notice
-and this permission notice appear in all copies.
-
-THE SOFTWARE IS PROVIDED "AS IS" AND THE AUTHOR DISCLAIMS ALL WARRANTIES WITH
-REGARD TO THIS SOFTWARE INCLUDING ALL IMPLIED WARRANTIES OF MERCHANTABILITY AND
-FITNESS. IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY SPECIAL, DIRECT,
-INDIRECT, OR CONSEQUENTIAL DAMAGES OR ANY DAMAGES WHATSOEVER RESULTING FROM LOSS
-OF USE, DATA OR PROFITS, WHETHER IN AN ACTION OF CONTRACT, NEGLIGENCE OR OTHER
-TORTIOUS ACTION, ARISING OUT OF OR IN CONNECTION WITH THE USE OR PERFORMANCE OF
-THIS SOFTWARE.
-]]
-
----
--- Lua functions for pandoc scripts.
---
--- @author Albert Krewinkel
--- @copyright © 2017–2019 Albert Krewinkel
--- @license MIT
-local M = {}
-
--- Re-export bundled modules
-M.List = require 'pandoc.List'
-M.mediabag = require 'pandoc.mediabag'
-M.system = require 'pandoc.system'
-M.types = require 'pandoc.types'
-M.utils = require 'pandoc.utils'
-M.text = require 'text'
-
--- Local names for modules which this module depends on.
-local List = M.List
-local utils = M.utils
-
-
-------------------------------------------------------------------------
--- Accessor objects
---
--- Create metatables which allow to access numerical indices via accessor
--- methods.
--- @section
--- @local
-
---- Create a new indexing function.
--- @param template function template
--- @param indices list of indices, starting with the most deeply nested
--- @return newly created function
--- @local
-function make_indexing_function(template, ...)
- local indices = {...}
- local loadstring = loadstring or load
- local bracketed = {}
- for i = 1, #indices do
- local idx = indices[#indices - i + 1]
- bracketed[i] = type(idx) == 'number'
- and string.format('[%d]', idx)
- or string.format('.%s', idx)
- end
- local fnstr = string.format('return ' .. template, table.concat(bracketed))
- return assert(loadstring(fnstr))()
-end
-
---- Create accessor functions using a function template.
--- @param fn_template function template in which '%s' is replacd with indices
--- @param accessors list of accessors
--- @return mapping from accessor names to accessor functions
--- @local
-local function create_accessor_functions (fn_template, accessors)
- local res = {}
- function add_accessors(acc, ...)
- if type(acc) == 'string' then
- res[acc] = make_indexing_function(fn_template, ...)
- elseif type(acc) == 'table' and #acc == 0 and next(acc) then
- -- Named substructure: the given names are accessed via the substructure,
- -- but the accessors are also added to the result table, enabling direct
- -- access from the parent element. Mainly used for `attr`.
- local name, substructure = next(acc)
- res[name] = make_indexing_function(fn_template, ...)
- for _, subname in ipairs(substructure) do
- res[subname] = make_indexing_function(fn_template, subname, ...)
- end
- else
- for i = 1, #(acc or {}) do
- add_accessors(acc[i], i, ...)
- end
- end
- end
- add_accessors(accessors)
- return res
-end
-
---- Get list of top-level fields from field descriptor table.
--- E.g.: `top_level_fields{'foo', {bar='baz'}, {'qux', 'quux'}}`
--- gives {'foo, 'bar', 'qux', 'quux'}
--- @local
-local function top_level_fields (fields)
- local result = List:new{}
- for _, v in ipairs(fields) do
- if type(v) == 'string' then
- table.insert(result, v)
- elseif type(v) == 'table' and #v == 0 and next(v) then
- table.insert(result, (next(v)))
- else
- result:extend(top_level_fields(v))
- end
- end
- return result
-end
-
---- Creates a function which behaves like next, but respects field names.
--- @local
-local function make_next_function (fields)
- local field_indices = {}
- for i, f in ipairs(fields) do
- field_indices[f] = i
- end
-
- return function (t, field)
- local raw_idx = field == nil and 0 or field_indices[field]
- local next_field = fields[raw_idx + 1]
- return next_field, t[next_field]
- end
-end
-
---- Create a new table which allows to access numerical indices via accessor
--- functions.
--- @local
-local function create_accessor_behavior (tag, accessors)
- local behavior = {tag = tag}
- behavior.getters = create_accessor_functions(
- 'function (x) return x.c%s end',
- accessors
- )
- behavior.setters = create_accessor_functions(
- 'function (x, v) x.c%s = v end',
- accessors
- )
- behavior.__eq = utils.equals
- behavior.__index = function(t, k)
- if getmetatable(t).getters[k] then
- return getmetatable(t).getters[k](t)
- elseif k == "t" then
- return getmetatable(t)["tag"]
- else
- return getmetatable(t)[k]
- end
- end
- behavior.__newindex = function(t, k, v)
- if getmetatable(t).setters[k] then
- getmetatable(t).setters[k](t, v)
- else
- rawset(t, k, v)
- end
- end
- behavior.__pairs = function (t)
- if accessors == nil then
- return next, t
- end
- local iterable_fields = type(accessors) == 'string'
- and {accessors}
- or top_level_fields(accessors)
- return make_next_function(iterable_fields), t
- end
- return behavior
-end
-
-
-------------------------------------------------------------------------
--- The base class for types
--- @type Type
--- @local
-local Type = {}
-Type.name = 'Type'
-Type.__index = Type
-Type.behavior = {
- __type = Type,
- new = function (obj)
- obj = obj or {}
- setmetatable(obj, self)
- return obj
- end
-}
-Type.behavior.__index = Type.behavior
-
---- Set a new behavior for the type, inheriting that of the parent type if none
---- is specified explicitly
--- @param behavior the behavior object for this type.
--- @local
-function Type:set_behavior (behavior)
- behavior = behavior or {}
- behavior.__index = rawget(behavior, '__index') or behavior
- behavior.__type = self
- if not getmetatable(behavior) and getmetatable(self) then
- setmetatable(behavior, getmetatable(self).behavior)
- end
- self.behavior = behavior
-end
-
---- Create a new subtype, using the given table as base.
--- @param name name of the new type
--- @param[opt] behavior behavioral object for the new type.
--- @return a new type
--- @local
-function Type:make_subtype(name, behavior)
- local newtype = setmetatable({}, self)
- newtype.name = name
- newtype.__index = newtype
- newtype:set_behavior(behavior)
- return newtype
-end
-
-
-------------------------------------------------------------------------
--- The base class for pandoc's AST elements.
--- @type AstElement
--- @local
-local AstElement = Type:make_subtype 'AstElement'
-AstElement.__call = function(t, ...)
- local success, ret = pcall(t.new, t, ...)
- if success then
- return setmetatable(ret, t.behavior)
- else
- error(string.format('Constructor for %s failed: %s\n', t.name, ret))
- end
-end
-
---- Make a new subtype which constructs a new value when called.
--- @local
-function AstElement:make_subtype(...)
- local newtype = Type.make_subtype(self, ...)
- newtype.__call = self.__call
- return newtype
-end
-
---- Create a new constructor
--- @local
--- @param tag Tag used to identify the constructor
--- @param fn Function to be called when constructing a new element
--- @param accessors names to use as accessors for numerical fields
--- @return function that constructs a new element
-function AstElement:create_constructor(tag, fn, accessors)
- local constr = self:make_subtype(tag, create_accessor_behavior(tag, accessors))
- function constr:new(...)
- return setmetatable(fn(...), self.behavior)
- end
- self.constructor = self.constructor or {}
- self.constructor[tag] = constr
- return constr
-end
-
---- Convert AstElement input into a list if necessary.
--- @local
-local function ensureList (x)
- if x.tag then
- -- Lists are not tagged, but all elements are
- return List:new{x}
- else
- return List:new(x)
- end
-end
-
---- Ensure a given object is an Inline element, or convert it into one.
--- @local
-local function ensureInlineList (x)
- if type(x) == 'string' then
- return List:new{M.Str(x)}
- else
- return ensureList(x)
- end
-end
-
---- Ensure that the given object is a definition pair, convert if necessary.
--- @local
-local function ensureDefinitionPairs (pair)
- local inlines = ensureInlineList(pair[1] or {})
- local blocks = ensureList(pair[2] or {}):map(ensureList)
- return {inlines, blocks}
-end
-
---- Split a string into it's words, using whitespace as separators.
-local function words (str)
- local ws = {}
- for w in str:gmatch("([^%s]+)") do ws[#ws + 1] = w end
- return ws
-end
-
---- Try hard to turn the arguments into an Attr object.
-local function ensureAttr(attr)
- if type(attr) == 'table' then
- if #attr > 0 then return M.Attr(table.unpack(attr)) end
-
- -- assume HTML-like key-value pairs
- local ident = attr.id or ''
- local classes = words(attr.class or '')
- local attributes = attr
- attributes.id = nil
- attributes.class = nil
- return M.Attr(ident, classes, attributes)
- elseif attr == nil then
- return M.Attr()
- elseif type(attr) == 'string' then
- -- treat argument as ID
- return M.Attr(attr)
- end
- -- print(arg, ...)
- error('Could not convert to Attr')
-end
-
-------------------------------------------------------------------------
---- Pandoc Document
--- @section document
-
---- A complete pandoc document
--- @function Pandoc
--- @tparam {Block,...} blocks document content
--- @tparam[opt] Meta meta document meta data
-M.Pandoc = AstElement:make_subtype'Pandoc'
-M.Pandoc.behavior.clone = M.types.clone.Pandoc
-function M.Pandoc:new (blocks, meta)
- return {
- blocks = ensureList(blocks),
- meta = meta or {},
- }
-end
-
--- DEPRECATED synonym:
-M.Doc = M.Pandoc
-
-------------------------------------------------------------------------
--- Meta
--- @section Meta
-
---- Create a new Meta object. It sets the metatable of the given table to
---- `Meta`.
--- @function Meta
--- @tparam meta table table containing document meta information
-M.Meta = AstElement:make_subtype'Meta'
-M.Meta.behavior.clone = M.types.clone.Meta
-function M.Meta:new (meta) return meta end
-
-
-------------------------------------------------------------------------
--- MetaValue
--- @section MetaValue
-M.MetaValue = AstElement:make_subtype('MetaValue')
-M.MetaValue.behavior.clone = M.types.clone.MetaValue
-
---- Meta blocks
--- @function MetaBlocks
--- @tparam {Block,...} blocks blocks
-M.MetaBlocks = M.MetaValue:create_constructor(
- 'MetaBlocks',
- function (content) return ensureList(content) end
-)
-
---- Meta inlines
--- @function MetaInlines
--- @tparam {Inline,...} inlines inlines
-M.MetaInlines = M.MetaValue:create_constructor(
- 'MetaInlines',
- function (content) return ensureInlineList(content) end
-)
-
---- Meta list
--- @function MetaList
--- @tparam {MetaValue,...} meta_values list of meta values
-M.MetaList = M.MetaValue:create_constructor(
- 'MetaList',
- function (content)
- if content.tag == 'MetaList' then
- return content
- end
- return ensureList(content)
- end
-)
-for k, v in pairs(List) do
- M.MetaList.behavior[k] = v
-end
-
---- Meta map
--- @function MetaMap
--- @tparam table key_value_map a string-indexed map of meta values
-M.MetaMap = M.MetaValue:create_constructor(
- "MetaMap",
- function (mm) return mm end
-)
-
---- Creates string to be used in meta data.
--- Does nothing, lua strings are meta strings.
--- @function MetaString
--- @tparam string str string value
-function M.MetaString(str)
- return str
-end
-
---- Creates boolean to be used in meta data.
--- Does nothing, lua booleans are meta booleans.
--- @function MetaBool
--- @tparam boolean bool boolean value
-function M.MetaBool(bool)
- return bool
-end
-
-------------------------------------------------------------------------
--- Blocks
--- @section Block
-
---- Block elements
-M.Block = AstElement:make_subtype'Block'
-M.Block.behavior.clone = M.types.clone.Block
-
---- Creates a block quote element
--- @function BlockQuote
--- @tparam {Block,...} content block content
--- @treturn Block block quote element
-M.BlockQuote = M.Block:create_constructor(
- "BlockQuote",
- function(content) return {c = ensureList(content)} end,
- "content"
-)
-
---- Creates a bullet (i.e. unordered) list.
--- @function BulletList
--- @tparam {{Block,...},...} content list of items
--- @treturn Block bullet list element
-M.BulletList = M.Block:create_constructor(
- "BulletList",
- function(content) return {c = ensureList(content):map(ensureList)} end,
- "content"
-)
-
---- Creates a code block element
--- @function CodeBlock
--- @tparam string text code string
--- @tparam[opt] Attr attr element attributes
--- @treturn Block code block element
-M.CodeBlock = M.Block:create_constructor(
- "CodeBlock",
- function(text, attr) return {c = {ensureAttr(attr), text}} end,
- {{attr = {"identifier", "classes", "attributes"}}, "text"}
-)
-
---- Creates a definition list, containing terms and their explanation.
--- @function DefinitionList
--- @tparam {{{Inline,...},{{Block,...}}},...} content list of items
--- @treturn Block definition list element
-M.DefinitionList = M.Block:create_constructor(
- "DefinitionList",
- function(content)
- return {c = ensureList(content):map(ensureDefinitionPairs)}
- end,
- "content"
-)
-
---- Creates a div element
--- @function Div
--- @tparam {Block,...} content block content
--- @tparam[opt] Attr attr element attributes
--- @treturn Block div element
-M.Div = M.Block:create_constructor(
- "Div",
- function(content, attr)
- return {c = {ensureAttr(attr), ensureList(content)}}
- end,
- {{attr = {"identifier", "classes", "attributes"}}, "content"}
-)
-
---- Creates a header element.
--- @function Header
--- @tparam int level header level
--- @tparam {Inline,...} content inline content
--- @tparam[opt] Attr attr element attributes
--- @treturn Block header element
-M.Header = M.Block:create_constructor(
- "Header",
- function(level, content, attr)
- return {c = {level, ensureAttr(attr), ensureInlineList(content)}}
- end,
- {"level", {attr = {"identifier", "classes", "attributes"}}, "content"}
-)
-
---- Creates a horizontal rule.
--- @function HorizontalRule
--- @treturn Block horizontal rule
-M.HorizontalRule = M.Block:create_constructor(
- "HorizontalRule",
- function() return {} end
-)
-
---- Creates a line block element.
--- @function LineBlock
--- @tparam {{Inline,...},...} content inline content
--- @treturn Block line block element
-M.LineBlock = M.Block:create_constructor(
- "LineBlock",
- function(content) return {c = ensureList(content):map(ensureInlineList)} end,
- "content"
-)
-
---- Creates a null element.
--- @function Null
--- @treturn Block null element
-M.Null = M.Block:create_constructor(
- "Null",
- function() return {} end
-)
-
---- Creates an ordered list.
--- @function OrderedList
--- @tparam {{Block,...},...} items list items
--- @param[opt] listAttributes list parameters
--- @treturn Block ordered list element
-M.OrderedList = M.Block:create_constructor(
- "OrderedList",
- function(items, listAttributes)
- listAttributes = listAttributes or M.ListAttributes()
- return {c = {listAttributes, ensureList(items):map(ensureList)}}
- end,
- {{listAttributes = {"start", "style", "delimiter"}}, "content"}
-)
-
---- Creates a para element.
--- @function Para
--- @tparam {Inline,...} content inline content
--- @treturn Block paragraph element
-M.Para = M.Block:create_constructor(
- "Para",
- function(content) return {c = ensureInlineList(content)} end,
- "content"
-)
-
---- Creates a plain element.
--- @function Plain
--- @tparam {Inline,...} content inline content
--- @treturn Block plain element
-M.Plain = M.Block:create_constructor(
- "Plain",
- function(content) return {c = ensureInlineList(content)} end,
- "content"
-)
-
---- Creates a raw content block of the specified format.
--- @function RawBlock
--- @tparam string format format of content
--- @tparam string text string content
--- @treturn Block raw block element
-M.RawBlock = M.Block:create_constructor(
- "RawBlock",
- function(format, text) return {c = {format, text}} end,
- {"format", "text"}
-)
-
---- Creates a table element.
--- @function Table
--- @tparam Caption caption table caption
--- @tparam {ColSpec,...} colspecs column alignments and widths
--- @tparam TableHead head table head
--- @tparam {TableBody,..} bodies table bodies
--- @treturn TableFoot foot table foot
--- @tparam[opt] Attr attr attributes
-M.Table = M.Block:create_constructor(
- "Table",
- function(caption, colspecs, head, bodies, foot, attr)
- return {
- c = {
- ensureAttr(attr),
- caption,
- List:new(colspecs),
- head,
- List:new(bodies),
- foot
- }
- }
- end,
- {"attr", "caption", "colspecs", "head", "bodies", "foot"}
-)
-
-
-------------------------------------------------------------------------
--- Inline
--- @section Inline
-
---- Inline element class
-M.Inline = AstElement:make_subtype'Inline'
-M.Inline.behavior.clone = M.types.clone.Inline
-
---- Creates a Cite inline element
--- @function Cite
--- @tparam {Inline,...} content List of inlines
--- @tparam {Citation,...} citations List of citations
--- @treturn Inline citations element
-M.Cite = M.Inline:create_constructor(
- "Cite",
- function(content, citations)
- return {c = {ensureList(citations), ensureInlineList(content)}}
- end,
- {"citations", "content"}
-)
-
---- Creates a Code inline element
--- @function Code
--- @tparam string text code string
--- @tparam[opt] Attr attr additional attributes
--- @treturn Inline code element
-M.Code = M.Inline:create_constructor(
- "Code",
- function(text, attr) return {c = {ensureAttr(attr), text}} end,
- {{attr = {"identifier", "classes", "attributes"}}, "text"}
-)
-
---- Creates an inline element representing emphasised text.
--- @function Emph
--- @tparam {Inline,..} content inline content
--- @treturn Inline emphasis element
-M.Emph = M.Inline:create_constructor(
- "Emph",
- function(content) return {c = ensureInlineList(content)} end,
- "content"
-)
-
---- Creates a Image inline element
--- @function Image
--- @tparam {Inline,..} caption text used to describe the image
--- @tparam string src path to the image file
--- @tparam[opt] string title brief image description
--- @tparam[opt] Attr attr additional attributes
--- @treturn Inline image element
-M.Image = M.Inline:create_constructor(
- "Image",
- function(caption, src, title, attr)
- title = title or ""
- return {c = {ensureAttr(attr), ensureInlineList(caption), {src, title}}}
- end,
- {{attr = {"identifier", "classes", "attributes"}}, "caption", {"src", "title"}}
-)
-
---- Create a LineBreak inline element
--- @function LineBreak
--- @treturn Inline linebreak element
-M.LineBreak = M.Inline:create_constructor(
- "LineBreak",
- function() return {} end
-)
-
---- Creates a link inline element, usually a hyperlink.
--- @function Link
--- @tparam {Inline,..} content text for this link
--- @tparam string target the link target
--- @tparam[opt] string title brief link description
--- @tparam[opt] Attr attr additional attributes
--- @treturn Inline image element
-M.Link = M.Inline:create_constructor(
- "Link",
- function(content, target, title, attr)
- title = title or ""
- attr = ensureAttr(attr)
- return {c = {attr, ensureInlineList(content), {target, title}}}
- end,
- {{attr = {"identifier", "classes", "attributes"}}, "content", {"target", "title"}}
-)
-
---- Creates a Math element, either inline or displayed.
--- @function Math
--- @tparam "InlineMath"|"DisplayMath" mathtype rendering specifier
--- @tparam string text Math content
--- @treturn Inline Math element
-M.Math = M.Inline:create_constructor(
- "Math",
- function(mathtype, text)
- return {c = {mathtype, text}}
- end,
- {"mathtype", "text"}
-)
---- Creates a DisplayMath element (DEPRECATED).
--- @function DisplayMath
--- @tparam string text Math content
--- @treturn Inline Math element
-M.DisplayMath = M.Inline:create_constructor(
- "DisplayMath",
- function(text) return M.Math("DisplayMath", text) end,
- {"mathtype", "text"}
-)
---- Creates an InlineMath inline element (DEPRECATED).
--- @function InlineMath
--- @tparam string text Math content
--- @treturn Inline Math element
-M.InlineMath = M.Inline:create_constructor(
- "InlineMath",
- function(text) return M.Math("InlineMath", text) end,
- {"mathtype", "text"}
-)
-
---- Creates a Note inline element
--- @function Note
--- @tparam {Block,...} content footnote block content
-M.Note = M.Inline:create_constructor(
- "Note",
- function(content) return {c = ensureList(content)} end,
- "content"
-)
-
---- Creates a Quoted inline element given the quote type and quoted content.
--- @function Quoted
--- @tparam "DoubleQuote"|"SingleQuote" quotetype type of quotes to be used
--- @tparam {Inline,..} content inline content
--- @treturn Inline quoted element
-M.Quoted = M.Inline:create_constructor(
- "Quoted",
- function(quotetype, content)
- return {c = {quotetype, ensureInlineList(content)}}
- end,
- {"quotetype", "content"}
-)
---- Creates a single-quoted inline element (DEPRECATED).
--- @function SingleQuoted
--- @tparam {Inline,..} content inline content
--- @treturn Inline quoted element
--- @see Quoted
-M.SingleQuoted = M.Inline:create_constructor(
- "SingleQuoted",
- function(content) return M.Quoted(M.SingleQuote, content) end,
- {"quotetype", "content"}
-)
---- Creates a single-quoted inline element (DEPRECATED).
--- @function DoubleQuoted
--- @tparam {Inline,..} content inline content
--- @treturn Inline quoted element
--- @see Quoted
-M.DoubleQuoted = M.Inline:create_constructor(
- "DoubleQuoted",
- function(content) return M.Quoted("DoubleQuote", content) end,
- {"quotetype", "content"}
-)
-
---- Creates a RawInline inline element
--- @function RawInline
--- @tparam string format format of the contents
--- @tparam string text string content
--- @treturn Inline raw inline element
-M.RawInline = M.Inline:create_constructor(
- "RawInline",
- function(format, text) return {c = {format, text}} end,
- {"format", "text"}
-)
-
---- Creates text rendered in small caps
--- @function SmallCaps
--- @tparam {Inline,..} content inline content
--- @treturn Inline smallcaps element
-M.SmallCaps = M.Inline:create_constructor(
- "SmallCaps",
- function(content) return {c = ensureInlineList(content)} end,
- "content"
-)
-
---- Creates a SoftBreak inline element.
--- @function SoftBreak
--- @treturn Inline softbreak element
-M.SoftBreak = M.Inline:create_constructor(
- "SoftBreak",
- function() return {} end
-)
-
---- Create a Space inline element
--- @function Space
--- @treturn Inline space element
-M.Space = M.Inline:create_constructor(
- "Space",
- function() return {} end
-)
-
---- Creates a Span inline element
--- @function Span
--- @tparam {Inline,..} content inline content
--- @tparam[opt] Attr attr additional attributes
--- @treturn Inline span element
-M.Span = M.Inline:create_constructor(
- "Span",
- function(content, attr)
- return {c = {ensureAttr(attr), ensureInlineList(content)}}
- end,
- {{attr = {"identifier", "classes", "attributes"}}, "content"}
-)
-
---- Creates a Str inline element
--- @function Str
--- @tparam string text content
--- @treturn Inline string element
-M.Str = M.Inline:create_constructor(
- "Str",
- function(text) return {c = text} end,
- "text"
-)
-
---- Creates text which is striked out.
--- @function Strikeout
--- @tparam {Inline,..} content inline content
--- @treturn Inline strikeout element
-M.Strikeout = M.Inline:create_constructor(
- "Strikeout",
- function(content) return {c = ensureInlineList(content)} end,
- "content"
-)
-
---- Creates a Strong element, whose text is usually displayed in a bold font.
--- @function Strong
--- @tparam {Inline,..} content inline content
--- @treturn Inline strong element
-M.Strong = M.Inline:create_constructor(
- "Strong",
- function(content) return {c = ensureInlineList(content)} end,
- "content"
-)
-
---- Creates a Subscript inline element
--- @function Subscript
--- @tparam {Inline,..} content inline content
--- @treturn Inline subscript element
-M.Subscript = M.Inline:create_constructor(
- "Subscript",
- function(content) return {c = ensureInlineList(content)} end,
- "content"
-)
-
---- Creates a Superscript inline element
--- @function Superscript
--- @tparam {Inline,..} content inline content
--- @treturn Inline superscript element
-M.Superscript = M.Inline:create_constructor(
- "Superscript",
- function(content) return {c = ensureInlineList(content)} end,
- "content"
-)
-
---- Creates an Underline inline element
--- @function Underline
--- @tparam {Inline,..} content inline content
--- @treturn Inline underline element
-M.Underline = M.Inline:create_constructor(
- "Underline",
- function(content) return {c = ensureInlineList(content)} end,
- "content"
-)
-
-
-------------------------------------------------------------------------
--- Element components
--- @section components
-
---- Check if the first element of a pair matches the given value.
--- @param x key value to be checked
--- @return function returning true iff first element of its argument matches x
--- @local
-local function assoc_key_equals (x)
- return function (y) return y[1] == x end
-end
-
---- Lookup a value in an associative list
--- @function lookup
--- @local
--- @tparam {{key, value},...} alist associative list
--- @param key key for which the associated value is to be looked up
-local function lookup(alist, key)
- return (List.find_if(alist, assoc_key_equals(key)) or {})[2]
-end
-
---- Return an iterator which returns key-value pairs of an associative list.
--- @function apairs
--- @local
--- @tparam {{key, value},...} alist associative list
-local apairs = function (alist)
- local i = 1
- local cur
- function nxt ()
- cur = rawget(alist, i)
- if cur then
- i = i + 1
- return cur[1], cur[2]
- end
- return nil
- end
- return nxt, nil, nil
-end
-
---- AttributeList, a metatable to allow table-like access to attribute lists
--- represented by associative lists.
--- @local
-local AttributeList = {
- __index = function (t, k)
- if type(k) == "number" then
- return rawget(t, k)
- else
- return lookup(t, k)
- end
- end,
-
- __newindex = function (t, k, v)
- local cur, idx = List.find_if(t, assoc_key_equals(k))
- if v == nil and not cur then
- -- deleted key does not exists in list
- return
- elseif v == nil then
- table.remove(t, idx)
- elseif cur then
- cur[2] = v
- elseif type(k) == "number" then
- rawset(t, k, v)
- else
- rawset(t, #t + 1, {k, v})
- end
- end,
-
- __pairs = apairs
-}
-
---- Convert a table to an associative list. The order of key-value pairs in the
--- alist is undefined. The table should either contain no numeric keys or
--- already be an associative list.
--- @local
--- @tparam table tbl associative list or table without numeric keys.
--- @treturn table associative list
-local to_alist = function (tbl)
- if #tbl ~= 0 or next(tbl) == nil then
- -- probably already an alist
- return tbl
- end
- local alist = {}
- local i = 1
- for k, v in pairs(tbl) do
- alist[i] = {k, v}
- i = i + 1
- end
- return alist
-end
-
--- Attr
-
---- Create a new set of attributes (Attr).
--- @function Attr
--- @tparam[opt] string identifier element identifier
--- @tparam[opt] {string,...} classes element classes
--- @tparam[opt] table attributes table containing string keys and values
--- @return element attributes
-M.Attr = AstElement:make_subtype'Attr'
-function M.Attr:new (identifier, classes, attributes)
- identifier = identifier or ''
- classes = ensureList(classes or {})
- attributes = setmetatable(to_alist(attributes or {}), AttributeList)
- return setmetatable({identifier, classes, attributes}, self.behavior)
-end
-M.Attr.behavior.clone = M.types.clone.Attr
-M.Attr.behavior.tag = 'Attr'
-M.Attr.behavior._field_names = {identifier = 1, classes = 2, attributes = 3}
-M.Attr.behavior.__eq = utils.equals
-M.Attr.behavior.__index = function(t, k)
- return (k == 't' and t.tag) or
- rawget(t, getmetatable(t)._field_names[k]) or
- getmetatable(t)[k]
-end
-M.Attr.behavior.__newindex = function(t, k, v)
- if k == 'attributes' then
- rawset(t, 3, setmetatable(to_alist(v or {}), AttributeList))
- elseif getmetatable(t)._field_names[k] then
- rawset(t, getmetatable(t)._field_names[k], v)
- else
- rawset(t, k, v)
- end
-end
-M.Attr.behavior.__pairs = function(t)
- local field_names = M.Attr.behavior._field_names
- local fields = {}
- for name, i in pairs(field_names) do
- fields[i] = name
- end
- return make_next_function(fields), t, nil
-end
-
--- Monkey-patch setters for `attr` fields to be more forgiving in the input that
--- results in a valid Attr value.
-function augment_attr_setter (setters)
- if setters.attr then
- local orig = setters.attr
- setters.attr = function(k, v)
- orig(k, ensureAttr(v))
- end
- end
-end
-for _, blk in pairs(M.Block.constructor) do
- augment_attr_setter(blk.behavior.setters)
-end
-for _, inln in pairs(M.Inline.constructor) do
- augment_attr_setter(inln.behavior.setters)
-end
-
-
--- Citation
-M.Citation = AstElement:make_subtype'Citation'
-M.Citation.behavior.clone = M.types.clone.Citation
-
---- Creates a single citation.
--- @function Citation
--- @tparam string id citation identifier (like a bibtex key)
--- @tparam AuthorInText|SuppressAuthor|NormalCitation mode citation mode
--- @tparam[opt] {Inline,...} prefix citation prefix
--- @tparam[opt] {Inline,...} suffix citation suffix
--- @tparam[opt] int note_num note number
--- @tparam[opt] int hash hash number
-function M.Citation:new (id, mode, prefix, suffix, note_num, hash)
- return {
- id = id,
- mode = mode,
- prefix = ensureList(prefix or {}),
- suffix = ensureList(suffix or {}),
- note_num = note_num or 0,
- hash = hash or 0,
- }
-end
-
--- ListAttributes
-M.ListAttributes = AstElement:make_subtype 'ListAttributes'
-M.ListAttributes.behavior.clone = M.types.clone.ListAttributes
-
---- Creates a set of list attributes.
--- @function ListAttributes
--- @tparam[opt] integer start number of the first list item
--- @tparam[opt] string style style used for list numbering
--- @tparam[opt] DefaultDelim|Period|OneParen|TwoParens delimiter delimiter of list numbers
--- @treturn table list attributes table
-function M.ListAttributes:new (start, style, delimiter)
- start = start or 1
- style = style or 'DefaultStyle'
- delimiter = delimiter or 'DefaultDelim'
- return {start, style, delimiter}
-end
-M.ListAttributes.behavior._field_names = {start = 1, style = 2, delimiter = 3}
-M.ListAttributes.behavior.__eq = utils.equals
-M.ListAttributes.behavior.__index = function (t, k)
- return rawget(t, getmetatable(t)._field_names[k]) or
- getmetatable(t)[k]
-end
-M.ListAttributes.behavior.__newindex = function (t, k, v)
- if getmetatable(t)._field_names[k] then
- rawset(t, getmetatable(t)._field_names[k], v)
- else
- rawset(t, k, v)
- end
-end
-M.ListAttributes.behavior.__pairs = function(t)
- local field_names = M.ListAttributes.behavior._field_names
- local fields = {}
- for name, i in pairs(field_names) do
- fields[i] = name
- end
- return make_next_function(fields), t, nil
-end
-
---
--- Legacy and compatibility types
---
-
---- Creates a simple (old style) table element.
--- @function SimpleTable
--- @tparam {Inline,...} caption table caption
--- @tparam {AlignDefault|AlignLeft|AlignRight|AlignCenter,...} aligns alignments
--- @tparam {int,...} widths column widths
--- @tparam {Block,...} headers header row
--- @tparam {{Block,...}} rows table rows
--- @treturn Block table element
-M.SimpleTable = function(caption, aligns, widths, headers, rows)
- return {
- caption = ensureInlineList(caption),
- aligns = List:new(aligns),
- widths = List:new(widths),
- headers = List:new(headers),
- rows = List:new(rows),
- tag = "SimpleTable",
- t = "SimpleTable",
- }
-end
-
-
-------------------------------------------------------------------------
--- Constants
--- @section constants
-
---- Author name is mentioned in the text.
--- @see Citation
--- @see Cite
-M.AuthorInText = "AuthorInText"
-
---- Author name is suppressed.
--- @see Citation
--- @see Cite
-M.SuppressAuthor = "SuppressAuthor"
-
---- Default citation style is used.
--- @see Citation
--- @see Cite
-M.NormalCitation = "NormalCitation"
-
---- Table cells aligned left.
--- @see Table
-M.AlignLeft = "AlignLeft"
-
---- Table cells right-aligned.
--- @see Table
-M.AlignRight = "AlignRight"
-
---- Table cell content is centered.
--- @see Table
-M.AlignCenter = "AlignCenter"
-
---- Table cells are alignment is unaltered.
--- @see Table
-M.AlignDefault = "AlignDefault"
-
---- Default list number delimiters are used.
--- @see OrderedList
-M.DefaultDelim = "DefaultDelim"
-
---- List numbers are delimited by a period.
--- @see OrderedList
-M.Period = "Period"
-
---- List numbers are delimited by a single parenthesis.
--- @see OrderedList
-M.OneParen = "OneParen"
-
---- List numbers are delimited by a double parentheses.
--- @see OrderedList
-M.TwoParens = "TwoParens"
-
---- List are numbered in the default style
--- @see OrderedList
-M.DefaultStyle = "DefaultStyle"
-
---- List items are numbered as examples.
--- @see OrderedList
-M.Example = "Example"
-
---- List are numbered using decimal integers.
--- @see OrderedList
-M.Decimal = "Decimal"
-
---- List are numbered using lower-case roman numerals.
--- @see OrderedList
-M.LowerRoman = "LowerRoman"
-
---- List are numbered using upper-case roman numerals
--- @see OrderedList
-M.UpperRoman = "UpperRoman"
-
---- List are numbered using lower-case alphabetic characters.
--- @see OrderedList
-M.LowerAlpha = "LowerAlpha"
-
---- List are numbered using upper-case alphabetic characters.
--- @see OrderedList
-M.UpperAlpha = "UpperAlpha"
-
-------------------------------------------------------------------------
--- Functions which have moved to different modules
-M.sha1 = utils.sha1
-
-return M
diff --git a/data/pptx/ppt/slideMasters/slideMaster1.xml b/data/pptx/ppt/slideMasters/slideMaster1.xml
index 69f0af019..2e0425358 100644
--- a/data/pptx/ppt/slideMasters/slideMaster1.xml
+++ b/data/pptx/ppt/slideMasters/slideMaster1.xml
@@ -1,2 +1,2 @@
<?xml version="1.0" encoding="UTF-8" standalone="yes"?>
-<p:sldMaster xmlns:a="http://schemas.openxmlformats.org/drawingml/2006/main" xmlns:r="http://schemas.openxmlformats.org/officeDocument/2006/relationships" xmlns:p="http://schemas.openxmlformats.org/presentationml/2006/main"><p:cSld><p:bg><p:bgRef idx="1001"><a:schemeClr val="bg1"/></p:bgRef></p:bg><p:spTree><p:nvGrpSpPr><p:cNvPr id="1" name=""/><p:cNvGrpSpPr/><p:nvPr/></p:nvGrpSpPr><p:grpSpPr><a:xfrm><a:off x="0" y="0"/><a:ext cx="0" cy="0"/><a:chOff x="0" y="0"/><a:chExt cx="0" cy="0"/></a:xfrm></p:grpSpPr><p:sp><p:nvSpPr><p:cNvPr id="2" name="Title Placeholder 1"/><p:cNvSpPr><a:spLocks noGrp="1"/></p:cNvSpPr><p:nvPr><p:ph type="title"/></p:nvPr></p:nvSpPr><p:spPr><a:xfrm><a:off x="457200" y="274638"/><a:ext cx="8229600" cy="1143000"/></a:xfrm><a:prstGeom prst="rect"><a:avLst/></a:prstGeom></p:spPr><p:txBody><a:bodyPr vert="horz" lIns="91440" tIns="45720" rIns="91440" bIns="45720" rtlCol="0" anchor="ctr"><a:normAutofit/></a:bodyPr><a:lstStyle/><a:p><a:r><a:rPr lang="en-US" smtClean="0"/><a:t>Click to edit Master title style</a:t></a:r><a:endParaRPr lang="en-US"/></a:p></p:txBody></p:sp><p:sp><p:nvSpPr><p:cNvPr id="3" name="Text Placeholder 2"/><p:cNvSpPr><a:spLocks noGrp="1"/></p:cNvSpPr><p:nvPr><p:ph type="body" idx="1"/></p:nvPr></p:nvSpPr><p:spPr><a:xfrm><a:off x="457200" y="1600200"/><a:ext cx="8229600" cy="4525963"/></a:xfrm><a:prstGeom prst="rect"><a:avLst/></a:prstGeom></p:spPr><p:txBody><a:bodyPr vert="horz" lIns="91440" tIns="45720" rIns="91440" bIns="45720" rtlCol="0"><a:normAutofit/></a:bodyPr><a:lstStyle/><a:p><a:pPr lvl="0"/><a:r><a:rPr lang="en-US" smtClean="0"/><a:t>Click to edit Master text styles</a:t></a:r></a:p><a:p><a:pPr lvl="1"/><a:r><a:rPr lang="en-US" smtClean="0"/><a:t>Second level</a:t></a:r></a:p><a:p><a:pPr lvl="2"/><a:r><a:rPr lang="en-US" smtClean="0"/><a:t>Third level</a:t></a:r></a:p><a:p><a:pPr lvl="3"/><a:r><a:rPr lang="en-US" smtClean="0"/><a:t>Fourth level</a:t></a:r></a:p><a:p><a:pPr lvl="4"/><a:r><a:rPr lang="en-US" smtClean="0"/><a:t>Fifth level</a:t></a:r><a:endParaRPr lang="en-US"/></a:p></p:txBody></p:sp><p:sp><p:nvSpPr><p:cNvPr id="4" name="Date Placeholder 3"/><p:cNvSpPr><a:spLocks noGrp="1"/></p:cNvSpPr><p:nvPr><p:ph type="dt" sz="half" idx="2"/></p:nvPr></p:nvSpPr><p:spPr><a:xfrm><a:off x="457200" y="6356350"/><a:ext cx="2133600" cy="365125"/></a:xfrm><a:prstGeom prst="rect"><a:avLst/></a:prstGeom></p:spPr><p:txBody><a:bodyPr vert="horz" lIns="91440" tIns="45720" rIns="91440" bIns="45720" rtlCol="0" anchor="ctr"/><a:lstStyle><a:lvl1pPr algn="l"><a:defRPr sz="1200"><a:solidFill><a:schemeClr val="tx1"><a:tint val="75000"/></a:schemeClr></a:solidFill></a:defRPr></a:lvl1pPr></a:lstStyle><a:p><a:fld id="{241EB5C9-1307-BA42-ABA2-0BC069CD8E7F}" type="datetimeFigureOut"><a:rPr lang="en-US" smtClean="0"/><a:t>4/5/2019</a:t></a:fld><a:endParaRPr lang="en-US"/></a:p></p:txBody></p:sp><p:sp><p:nvSpPr><p:cNvPr id="5" name="Footer Placeholder 4"/><p:cNvSpPr><a:spLocks noGrp="1"/></p:cNvSpPr><p:nvPr><p:ph type="ftr" sz="quarter" idx="3"/></p:nvPr></p:nvSpPr><p:spPr><a:xfrm><a:off x="3124200" y="6356350"/><a:ext cx="2895600" cy="365125"/></a:xfrm><a:prstGeom prst="rect"><a:avLst/></a:prstGeom></p:spPr><p:txBody><a:bodyPr vert="horz" lIns="91440" tIns="45720" rIns="91440" bIns="45720" rtlCol="0" anchor="ctr"/><a:lstStyle><a:lvl1pPr algn="ctr"><a:defRPr sz="1200"><a:solidFill><a:schemeClr val="tx1"><a:tint val="75000"/></a:schemeClr></a:solidFill></a:defRPr></a:lvl1pPr></a:lstStyle><a:p><a:endParaRPr lang="en-US"/></a:p></p:txBody></p:sp><p:sp><p:nvSpPr><p:cNvPr id="6" name="Slide Number Placeholder 5"/><p:cNvSpPr><a:spLocks noGrp="1"/></p:cNvSpPr><p:nvPr><p:ph type="sldNum" sz="quarter" idx="4"/></p:nvPr></p:nvSpPr><p:spPr><a:xfrm><a:off x="6553200" y="6356350"/><a:ext cx="2133600" cy="365125"/></a:xfrm><a:prstGeom prst="rect"><a:avLst/></a:prstGeom></p:spPr><p:txBody><a:bodyPr vert="horz" lIns="91440" tIns="45720" rIns="91440" bIns="45720" rtlCol="0" anchor="ctr"/><a:lstStyle><a:lvl1pPr algn="r"><a:defRPr sz="1200"><a:solidFill><a:schemeClr val="tx1"><a:tint val="75000"/></a:schemeClr></a:solidFill></a:defRPr></a:lvl1pPr></a:lstStyle><a:p><a:fld id="{C5EF2332-01BF-834F-8236-50238282D533}" type="slidenum"><a:rPr lang="en-US" smtClean="0"/><a:t>‹#›</a:t></a:fld><a:endParaRPr lang="en-US"/></a:p></p:txBody></p:sp></p:spTree><p:extLst><p:ext uri="{BB962C8B-B14F-4D97-AF65-F5344CB8AC3E}"><p14:creationId xmlns:p14="http://schemas.microsoft.com/office/powerpoint/2010/main" val="3676200875"/></p:ext></p:extLst></p:cSld><p:clrMap bg1="lt1" tx1="dk1" bg2="lt2" tx2="dk2" accent1="accent1" accent2="accent2" accent3="accent3" accent4="accent4" accent5="accent5" accent6="accent6" hlink="hlink" folHlink="folHlink"/><p:sldLayoutIdLst><p:sldLayoutId id="2147483649" r:id="rId1"/><p:sldLayoutId id="2147483650" r:id="rId2"/><p:sldLayoutId id="2147483651" r:id="rId3"/><p:sldLayoutId id="2147483652" r:id="rId4"/><p:sldLayoutId id="2147483653" r:id="rId5"/><p:sldLayoutId id="2147483654" r:id="rId6"/><p:sldLayoutId id="2147483655" r:id="rId7"/><p:sldLayoutId id="2147483656" r:id="rId8"/><p:sldLayoutId id="2147483657" r:id="rId9"/><p:sldLayoutId id="2147483658" r:id="rId10"/><p:sldLayoutId id="2147483659" r:id="rId11"/></p:sldLayoutIdLst><p:txStyles><p:titleStyle><a:lvl1pPr algn="ctr" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:spcBef><a:spcPct val="0"/></a:spcBef><a:buNone/><a:defRPr sz="4400" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mj-lt"/><a:ea typeface="+mj-ea"/><a:cs typeface="+mj-cs"/></a:defRPr></a:lvl1pPr></p:titleStyle><p:bodyStyle><a:lvl1pPr marL="342900" indent="-342900" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:spcBef><a:spcPct val="20000"/></a:spcBef><a:buFont typeface="Arial"/><a:buChar char="•"/><a:defRPr sz="3200" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl1pPr><a:lvl2pPr marL="742950" indent="-285750" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:spcBef><a:spcPct val="20000"/></a:spcBef><a:buFont typeface="Arial"/><a:buChar char="–"/><a:defRPr sz="2800" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl2pPr><a:lvl3pPr marL="1143000" indent="-228600" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:spcBef><a:spcPct val="20000"/></a:spcBef><a:buFont typeface="Arial"/><a:buChar char="•"/><a:defRPr sz="2400" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl3pPr><a:lvl4pPr marL="1600200" indent="-228600" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:spcBef><a:spcPct val="20000"/></a:spcBef><a:buFont typeface="Arial"/><a:buChar char="–"/><a:defRPr sz="2000" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl4pPr><a:lvl5pPr marL="2057400" indent="-228600" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:spcBef><a:spcPct val="20000"/></a:spcBef><a:buFont typeface="Arial"/><a:buChar char="»"/><a:defRPr sz="2000" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl5pPr><a:lvl6pPr marL="2514600" indent="-228600" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:spcBef><a:spcPct val="20000"/></a:spcBef><a:buFont typeface="Arial"/><a:buChar char="•"/><a:defRPr sz="2000" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl6pPr><a:lvl7pPr marL="2971800" indent="-228600" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:spcBef><a:spcPct val="20000"/></a:spcBef><a:buFont typeface="Arial"/><a:buChar char="•"/><a:defRPr sz="2000" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl7pPr><a:lvl8pPr marL="3429000" indent="-228600" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:spcBef><a:spcPct val="20000"/></a:spcBef><a:buFont typeface="Arial"/><a:buChar char="•"/><a:defRPr sz="2000" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl8pPr><a:lvl9pPr marL="3886200" indent="-228600" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:spcBef><a:spcPct val="20000"/></a:spcBef><a:buFont typeface="Arial"/><a:buChar char="•"/><a:defRPr sz="2000" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl9pPr></p:bodyStyle><p:otherStyle><a:defPPr><a:defRPr lang="en-US"/></a:defPPr><a:lvl1pPr marL="0" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:defRPr sz="1800" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl1pPr><a:lvl2pPr marL="457200" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:defRPr sz="1800" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl2pPr><a:lvl3pPr marL="914400" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:defRPr sz="1800" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl3pPr><a:lvl4pPr marL="1371600" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:defRPr sz="1800" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl4pPr><a:lvl5pPr marL="1828800" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:defRPr sz="1800" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl5pPr><a:lvl6pPr marL="2286000" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:defRPr sz="1800" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl6pPr><a:lvl7pPr marL="2743200" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:defRPr sz="1800" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl7pPr><a:lvl8pPr marL="3200400" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:defRPr sz="1800" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl8pPr><a:lvl9pPr marL="3657600" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:defRPr sz="1800" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl9pPr></p:otherStyle></p:txStyles></p:sldMaster> \ No newline at end of file
+<p:sldMaster xmlns:a="http://schemas.openxmlformats.org/drawingml/2006/main" xmlns:r="http://schemas.openxmlformats.org/officeDocument/2006/relationships" xmlns:p="http://schemas.openxmlformats.org/presentationml/2006/main"><p:cSld><p:bg><p:bgRef idx="1001"><a:schemeClr val="bg1"/></p:bgRef></p:bg><p:spTree><p:nvGrpSpPr><p:cNvPr id="1" name=""/><p:cNvGrpSpPr/><p:nvPr/></p:nvGrpSpPr><p:grpSpPr><a:xfrm><a:off x="0" y="0"/><a:ext cx="0" cy="0"/><a:chOff x="0" y="0"/><a:chExt cx="0" cy="0"/></a:xfrm></p:grpSpPr><p:sp><p:nvSpPr><p:cNvPr id="2" name="Title Placeholder 1"/><p:cNvSpPr><a:spLocks noGrp="1"/></p:cNvSpPr><p:nvPr><p:ph type="title"/></p:nvPr></p:nvSpPr><p:spPr><a:xfrm><a:off x="457200" y="274638"/><a:ext cx="8229600" cy="1143000"/></a:xfrm><a:prstGeom prst="rect"><a:avLst/></a:prstGeom></p:spPr><p:txBody><a:bodyPr vert="horz" lIns="91440" tIns="45720" rIns="91440" bIns="45720" rtlCol="0" anchor="ctr"><a:normAutofit/></a:bodyPr><a:lstStyle/><a:p><a:r><a:rPr lang="en-US" smtClean="0"/><a:t>Click to edit Master title style</a:t></a:r><a:endParaRPr lang="en-US"/></a:p></p:txBody></p:sp><p:sp><p:nvSpPr><p:cNvPr id="3" name="Text Placeholder 2"/><p:cNvSpPr><a:spLocks noGrp="1"/></p:cNvSpPr><p:nvPr><p:ph type="body" idx="1"/></p:nvPr></p:nvSpPr><p:spPr><a:xfrm><a:off x="457200" y="1600200"/><a:ext cx="8229600" cy="4525963"/></a:xfrm><a:prstGeom prst="rect"><a:avLst/></a:prstGeom></p:spPr><p:txBody><a:bodyPr vert="horz" lIns="91440" tIns="45720" rIns="91440" bIns="45720" rtlCol="0"><a:normAutofit/></a:bodyPr><a:lstStyle/><a:p><a:pPr lvl="0"/><a:r><a:rPr lang="en-US" smtClean="0"/><a:t>Click to edit Master text styles</a:t></a:r></a:p><a:p><a:pPr lvl="1"/><a:r><a:rPr lang="en-US" smtClean="0"/><a:t>Second level</a:t></a:r></a:p><a:p><a:pPr lvl="2"/><a:r><a:rPr lang="en-US" smtClean="0"/><a:t>Third level</a:t></a:r></a:p><a:p><a:pPr lvl="3"/><a:r><a:rPr lang="en-US" smtClean="0"/><a:t>Fourth level</a:t></a:r></a:p><a:p><a:pPr lvl="4"/><a:r><a:rPr lang="en-US" smtClean="0"/><a:t>Fifth level</a:t></a:r><a:endParaRPr lang="en-US"/></a:p></p:txBody></p:sp><p:sp><p:nvSpPr><p:cNvPr id="4" name="Date Placeholder 3"/><p:cNvSpPr><a:spLocks noGrp="1"/></p:cNvSpPr><p:nvPr><p:ph type="dt" sz="half" idx="2"/></p:nvPr></p:nvSpPr><p:spPr><a:xfrm><a:off x="457200" y="6356350"/><a:ext cx="2133600" cy="365125"/></a:xfrm><a:prstGeom prst="rect"><a:avLst/></a:prstGeom></p:spPr><p:txBody><a:bodyPr vert="horz" lIns="91440" tIns="45720" rIns="91440" bIns="45720" rtlCol="0" anchor="ctr"/><a:lstStyle><a:lvl1pPr algn="l"><a:defRPr sz="1200"><a:solidFill><a:schemeClr val="tx1"><a:tint val="75000"/></a:schemeClr></a:solidFill></a:defRPr></a:lvl1pPr></a:lstStyle><a:p><a:fld id="{241EB5C9-1307-BA42-ABA2-0BC069CD8E7F}" type="datetimeFigureOut"><a:rPr lang="en-US" smtClean="0"/><a:t>4/5/2019</a:t></a:fld><a:endParaRPr lang="en-US"/></a:p></p:txBody></p:sp><p:sp><p:nvSpPr><p:cNvPr id="5" name="Footer Placeholder 4"/><p:cNvSpPr><a:spLocks noGrp="1"/></p:cNvSpPr><p:nvPr><p:ph type="ftr" sz="quarter" idx="3"/></p:nvPr></p:nvSpPr><p:spPr><a:xfrm><a:off x="3124200" y="6356350"/><a:ext cx="2895600" cy="365125"/></a:xfrm><a:prstGeom prst="rect"><a:avLst/></a:prstGeom></p:spPr><p:txBody><a:bodyPr vert="horz" lIns="91440" tIns="45720" rIns="91440" bIns="45720" rtlCol="0" anchor="ctr"/><a:lstStyle><a:lvl1pPr algn="ctr"><a:defRPr sz="1200"><a:solidFill><a:schemeClr val="tx1"><a:tint val="75000"/></a:schemeClr></a:solidFill></a:defRPr></a:lvl1pPr></a:lstStyle><a:p><a:endParaRPr lang="en-US"/></a:p></p:txBody></p:sp><p:sp><p:nvSpPr><p:cNvPr id="6" name="Slide Number Placeholder 5"/><p:cNvSpPr><a:spLocks noGrp="1"/></p:cNvSpPr><p:nvPr><p:ph type="sldNum" sz="quarter" idx="4"/></p:nvPr></p:nvSpPr><p:spPr><a:xfrm><a:off x="6553200" y="6356350"/><a:ext cx="2133600" cy="365125"/></a:xfrm><a:prstGeom prst="rect"><a:avLst/></a:prstGeom></p:spPr><p:txBody><a:bodyPr vert="horz" lIns="91440" tIns="45720" rIns="91440" bIns="45720" rtlCol="0" anchor="ctr"/><a:lstStyle><a:lvl1pPr algn="r"><a:defRPr sz="1200"><a:solidFill><a:schemeClr val="tx1"><a:tint val="75000"/></a:schemeClr></a:solidFill></a:defRPr></a:lvl1pPr></a:lstStyle><a:p><a:fld id="{C5EF2332-01BF-834F-8236-50238282D533}" type="slidenum"><a:rPr lang="en-US" smtClean="0"/><a:t>‹#›</a:t></a:fld><a:endParaRPr lang="en-US"/></a:p></p:txBody></p:sp></p:spTree><p:extLst><p:ext uri="{BB962C8B-B14F-4D97-AF65-F5344CB8AC3E}"><p14:creationId xmlns:p14="http://schemas.microsoft.com/office/powerpoint/2010/main" val="3676200875"/></p:ext></p:extLst></p:cSld><p:clrMap bg1="lt1" tx1="dk1" bg2="lt2" tx2="dk2" accent1="accent1" accent2="accent2" accent3="accent3" accent4="accent4" accent5="accent5" accent6="accent6" hlink="hlink" folHlink="folHlink"/><p:sldLayoutIdLst><p:sldLayoutId id="2147483649" r:id="rId1"/><p:sldLayoutId id="2147483650" r:id="rId2"/><p:sldLayoutId id="2147483651" r:id="rId3"/><p:sldLayoutId id="2147483652" r:id="rId4"/><p:sldLayoutId id="2147483653" r:id="rId5"/><p:sldLayoutId id="2147483654" r:id="rId6"/><p:sldLayoutId id="2147483655" r:id="rId7"/><p:sldLayoutId id="2147483656" r:id="rId8"/><p:sldLayoutId id="2147483657" r:id="rId9"/><p:sldLayoutId id="2147483658" r:id="rId10"/><p:sldLayoutId id="2147483659" r:id="rId11"/></p:sldLayoutIdLst><p:txStyles><p:titleStyle><a:lvl1pPr algn="ctr" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:spcBef><a:spcPct val="0"/></a:spcBef><a:buNone/><a:defRPr sz="4400" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mj-lt"/><a:ea typeface="+mj-ea"/><a:cs typeface="+mj-cs"/></a:defRPr></a:lvl1pPr></p:titleStyle><p:bodyStyle><a:lvl1pPr marL="457200" indent="-457200" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:spcBef><a:spcPct val="20000"/></a:spcBef><a:buFont typeface="Arial"/><a:buChar char="•"/><a:defRPr sz="3200" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl1pPr><a:lvl2pPr marL="914400" indent="-457200" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:spcBef><a:spcPct val="20000"/></a:spcBef><a:buFont typeface="Arial"/><a:buChar char="–"/><a:defRPr sz="2800" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl2pPr><a:lvl3pPr marL="1371600" indent="-457200" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:spcBef><a:spcPct val="20000"/></a:spcBef><a:buFont typeface="Arial"/><a:buChar char="•"/><a:defRPr sz="2400" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl3pPr><a:lvl4pPr marL="1828800" indent="-457200" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:spcBef><a:spcPct val="20000"/></a:spcBef><a:buFont typeface="Arial"/><a:buChar char="–"/><a:defRPr sz="2000" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl4pPr><a:lvl5pPr marL="2286000" indent="-457200" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:spcBef><a:spcPct val="20000"/></a:spcBef><a:buFont typeface="Arial"/><a:buChar char="»"/><a:defRPr sz="2000" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl5pPr><a:lvl6pPr marL="2743200" indent="-457200" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:spcBef><a:spcPct val="20000"/></a:spcBef><a:buFont typeface="Arial"/><a:buChar char="•"/><a:defRPr sz="2000" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl6pPr><a:lvl7pPr marL="3200400" indent="-457200" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:spcBef><a:spcPct val="20000"/></a:spcBef><a:buFont typeface="Arial"/><a:buChar char="•"/><a:defRPr sz="2000" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl7pPr><a:lvl8pPr marL="3657600" indent="-457200" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:spcBef><a:spcPct val="20000"/></a:spcBef><a:buFont typeface="Arial"/><a:buChar char="•"/><a:defRPr sz="2000" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl8pPr><a:lvl9pPr marL="4114800" indent="-457200" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:spcBef><a:spcPct val="20000"/></a:spcBef><a:buFont typeface="Arial"/><a:buChar char="•"/><a:defRPr sz="2000" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl9pPr></p:bodyStyle><p:otherStyle><a:defPPr><a:defRPr lang="en-US"/></a:defPPr><a:lvl1pPr marL="0" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:defRPr sz="1800" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl1pPr><a:lvl2pPr marL="457200" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:defRPr sz="1800" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl2pPr><a:lvl3pPr marL="914400" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:defRPr sz="1800" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl3pPr><a:lvl4pPr marL="1371600" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:defRPr sz="1800" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl4pPr><a:lvl5pPr marL="1828800" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:defRPr sz="1800" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl5pPr><a:lvl6pPr marL="2286000" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:defRPr sz="1800" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl6pPr><a:lvl7pPr marL="2743200" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:defRPr sz="1800" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl7pPr><a:lvl8pPr marL="3200400" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:defRPr sz="1800" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl8pPr><a:lvl9pPr marL="3657600" algn="l" defTabSz="457200" rtl="0" eaLnBrk="1" latinLnBrk="0" hangingPunct="1"><a:defRPr sz="1800" kern="1200"><a:solidFill><a:schemeClr val="tx1"/></a:solidFill><a:latin typeface="+mn-lt"/><a:ea typeface="+mn-ea"/><a:cs typeface="+mn-cs"/></a:defRPr></a:lvl9pPr></p:otherStyle></p:txStyles></p:sldMaster>
diff --git a/data/sample.lua b/data/sample.lua
index b87848378..ea20add2e 100644
--- a/data/sample.lua
+++ b/data/sample.lua
@@ -143,7 +143,7 @@ end
function Link(s, tgt, tit, attr)
return "<a href='" .. escape(tgt,true) .. "' title='" ..
- escape(tit,true) .. "'>" .. s .. "</a>"
+ escape(tit,true) .. "'" .. attributes(attr) .. ">" .. s .. "</a>"
end
function Image(s, src, tit, attr)
@@ -284,9 +284,15 @@ local function html_align(align)
end
function CaptionedImage(src, tit, caption, attr)
- return '<div class="figure">\n<img src="' .. escape(src,true) ..
- '" title="' .. escape(tit,true) .. '"/>\n' ..
- '<p class="caption">' .. escape(caption) .. '</p>\n</div>'
+ if #caption == 0 then
+ return '<p><img src="' .. escape(src,true) .. '" id="' .. attr.id ..
+ '"/></p>'
+ else
+ local ecaption = escape(caption)
+ return '<figure>\n<img src="' .. escape(src,true) ..
+ '" id="' .. attr.id .. '" alt="' .. ecaption .. '"/>' ..
+ '<figcaption>' .. ecaption .. '</figcaption>\n</figure>'
+ end
end
-- Caption is a string, aligns is an array of strings,
@@ -299,7 +305,7 @@ function Table(caption, aligns, widths, headers, rows)
end
add("<table>")
if caption ~= "" then
- add("<caption>" .. caption .. "</caption>")
+ add("<caption>" .. escape(caption) .. "</caption>")
end
if widths and widths[1] ~= 0 then
for _, w in pairs(widths) do
@@ -313,9 +319,7 @@ function Table(caption, aligns, widths, headers, rows)
table.insert(header_row,'<th align="' .. align .. '">' .. h .. '</th>')
empty_header = empty_header and h == ""
end
- if empty_header then
- head = ""
- else
+ if not empty_header then
add('<tr class="header">')
for _,h in pairs(header_row) do
add(h)
diff --git a/data/templates/affiliations.jats b/data/templates/affiliations.jats
index 93238d22e..17c3cf164 100644
--- a/data/templates/affiliations.jats
+++ b/data/templates/affiliations.jats
@@ -1,38 +1,36 @@
$--
$-- Affiliations
$--
-$for(affiliation)$
-<aff id="aff-$affiliation.id$">
+<aff id="aff-$it.id$">
$-- wrap affiliation if it has a known institution identifier
-$if(affiliation.group)$
-<institution content-type="group">$affiliation.group$</institution>
+$if(it.group)$
+<institution content-type="group">${it.group}</institution>
$endif$
-$if(affiliation.department)$
-<institution content-type="dept">$affiliation.department$</institution>
+$if(it.department)$
+<institution content-type="dept">${it.department}</institution>
$endif$
<institution-wrap>
-$if(affiliation.organization)$
-<institution>$affiliation.organization$</institution>
+$if(it.organization)$
+<institution>${it.organization}</institution>
$else$
-<institution>$affiliation.name$</institution>
+<institution>${it.name}</institution>
$endif$
-$if(affiliation.isni)$
-<institution-id institution-id-type="ISNI">$affiliation.isni$</institution-id>
+$if(it.isni)$
+<institution-id institution-id-type="ISNI">${it.isni}</institution-id>
$endif$
-$if(affiliation.ringgold)$
-<institution-id institution-id-type="Ringgold">$affiliation.ringgold$</institution-id>
+$if(it.ringgold)$
+<institution-id institution-id-type="Ringgold">${it.ringgold}</institution-id>
$endif$
-$if(affiliation.ror)$
-<institution-id institution-id-type="ROR">$affiliation.ror$</institution-id>
+$if(it.ror)$
+<institution-id institution-id-type="ROR">${it.ror}</institution-id>
$endif$
-$for(affiliation.pid)$
-<institution-id institution-id-type="$affiliation.pid.type$">$affiliation.pid.id$</institution-id>
+$for(it.pid)$
+<institution-id institution-id-type="${it.type}">${it.id}</institution-id>
$endfor$
-</institution-wrap>$if(affiliation.street-address)$,
-$for(affiliation.street-address)$
-<addr-line>$affiliation.street-address$</addr-line>$sep$,
+</institution-wrap>$if(it.street-address)$,
+$for(it.street-address)$
+<addr-line>${it}</addr-line>$sep$,
$endfor$
-$else$$if(affiliation.city)$, <city>$affiliation.city$</city>$endif$$endif$$if(affiliation.country)$,
-<country$if(affiliation.country-code)$ country="$affiliation.country-code$"$endif$>$affiliation.country$</country>$endif$
+$else$$if(it.city)$, <city>$it.city$</city>$endif$$endif$$if(it.country)$,
+<country$if(it.country-code)$ country="$it.country-code$"$endif$>$it.country$</country>$endif$
</aff>
-$endfor$
diff --git a/data/templates/article.jats_publishing b/data/templates/article.jats_publishing
index 9bedff6af..47ab8f197 100644
--- a/data/templates/article.jats_publishing
+++ b/data/templates/article.jats_publishing
@@ -81,12 +81,15 @@ $endif$
$if(title)$
<title-group>
<article-title>$title$</article-title>
+$if(subtitle)$
+<subtitle>${subtitle}</subtitle>
+$endif$
</title-group>
$endif$
$if(author)$
<contrib-group>
$for(author)$
-<contrib contrib-type="author"$if(author.equal-contrib)$ equal-contrib="true"$endif$>
+<contrib contrib-type="author"$if(author.equal-contrib)$ equal-contrib="yes"$endif$>
$if(author.orcid)$
<contrib-id contrib-id-type="orcid">$author.orcid$</contrib-id>
$endif$
@@ -103,15 +106,25 @@ $endif$
$if(author.email)$
<email>$author.email$</email>
$endif$
+$-- if affiliations are listed separately, then create links. Otherwise
+$-- include them here.
+$if(affiliation)$
$for(author.affiliation)$
<xref ref-type="aff" rid="aff-$author.affiliation$"/>
$endfor$
+$else$
+$for(author.affiliation)$
+${ it:affiliations.jats() }
+$endfor$
+$endif$
$if(author.cor-id)$
<xref ref-type="corresp" rid="cor-$author.cor-id$"><sup>*</sup></xref>
$endif$
</contrib>
$endfor$
-${ affiliations.jats() }
+$for(affiliation)$
+${ it:affiliations.jats() }
+$endfor$
</contrib-group>
$endif$
$if(article.author-notes)$
diff --git a/data/templates/default.jats_articleauthoring b/data/templates/default.jats_articleauthoring
index 60b2ca559..01042b001 100644
--- a/data/templates/default.jats_articleauthoring
+++ b/data/templates/default.jats_articleauthoring
@@ -14,12 +14,15 @@ $endif$
$if(title)$
<title-group>
<article-title>$title$</article-title>
+$if(subtitle)$
+<subtitle>${subtitle}</subtitle>
+$endif$
</title-group>
$endif$
$if(author)$
<contrib-group>
$for(author)$
-<contrib contrib-type="author"$if(author.equal-contrib)$ equal-contrib="true"$endif$>
+<contrib contrib-type="author"$if(author.equal-contrib)$ equal-contrib="yes"$endif$>
$if(author.orcid)$
<contrib-id contrib-id-type="orcid">$author.orcid$</contrib-id>
$endif$
@@ -33,18 +36,17 @@ $elseif(author.name)$
$else$
<string-name>$author$</string-name>
$endif$
+$for(author.affiliation)$
+${ it:affiliations.jats() }
+$endfor$
$if(author.email)$
<email>$author.email$</email>
$endif$
-$for(author.affiliation)$
-<xref ref-type="aff" rid="aff-$author.affiliation$"/>
-$endfor$
$if(author.cor-id)$
<xref ref-type="corresp" rid="cor-$author.cor-id$"><sup>*</sup></xref>
$endif$
</contrib>
$endfor$
-${ affiliations.jats() }
</contrib-group>
$endif$
$if(copyright)$
diff --git a/data/templates/default.latex b/data/templates/default.latex
index d06701675..3874813c7 100644
--- a/data/templates/default.latex
+++ b/data/templates/default.latex
@@ -4,11 +4,6 @@
$if(colorlinks)$
\PassOptionsToPackage{dvipsnames,svgnames,x11names}{xcolor}
$endif$
-$if(dir)$
-$if(latex-dir-rtl)$
-\PassOptionsToPackage{RTLdocument}{bidi}
-$endif$
-$endif$
$if(CJKmainfont)$
\PassOptionsToPackage{space}{xeCJK}
$endif$
@@ -17,9 +12,6 @@ $endif$
$if(fontsize)$
$fontsize$,
$endif$
-$if(lang)$
- $babel-lang$,
-$endif$
$if(papersize)$
$papersize$paper,
$endif$
@@ -315,6 +307,7 @@ $if(links-as-notes)$
\DeclareRobustCommand{\href}[2]{#2\footnote{\url{#1}}}
$endif$
$if(strikeout)$
+$-- also used for underline
\usepackage[normalem]{ulem}
% Avoid problems with \sout in headers with hyperref
\pdfstringdefDisableCommands{\renewcommand{\sout}{}}
@@ -369,35 +362,27 @@ $if(csl-refs)$
\newcommand{\CSLRightInline}[1]{\parbox[t]{\linewidth - \csllabelwidth}{#1}\break}
\newcommand{\CSLIndent}[1]{\hspace{\cslhangindent}#1}
$endif$
-$for(header-includes)$
-$header-includes$
-$endfor$
$if(lang)$
-\ifXeTeX
- % Load polyglossia as late as possible: uses bidi with RTL langages (e.g. Hebrew, Arabic)
- \usepackage{polyglossia}
- \setmainlanguage[$for(polyglossia-lang.options)$$polyglossia-lang.options$$sep$,$endfor$]{$polyglossia-lang.name$}
-$for(polyglossia-otherlangs)$
- \setotherlanguage[$for(polyglossia-otherlangs.options)$$polyglossia-otherlangs.options$$sep$,$endfor$]{$polyglossia-otherlangs.name$}
-$endfor$
+\ifLuaTeX
+\usepackage[bidi=basic]{babel}
\else
- \usepackage[$for(babel-otherlangs)$$babel-otherlangs$,$endfor$main=$babel-lang$]{babel}
+\usepackage[bidi=default]{babel}
+\fi
+\babelprovide[main,import]{$babel-lang$}
+$for(babel-otherlangs)$
+\babelprovide[import]{$babel-otherlangs$}
+$endfor$
% get rid of language-specific shorthands (see #6817):
\let\LanguageShortHands\languageshorthands
\def\languageshorthands#1{}
-$if(babel-newcommands)$
- $babel-newcommands$
-$endif$
-\fi
$endif$
+$for(header-includes)$
+$header-includes$
+$endfor$
\ifLuaTeX
\usepackage{selnolig} % disable illegal ligatures
\fi
$if(dir)$
-\ifXeTeX
- % Load bidi as late as possible as it modifies e.g. graphicx
- \usepackage{bidi}
-\fi
\ifPDFTeX
\TeXXeTstate=1
\newcommand{\RL}[1]{\beginR #1\endR}
diff --git a/data/templates/default.markua b/data/templates/default.markua
new file mode 100644
index 000000000..9f6ca96de
--- /dev/null
+++ b/data/templates/default.markua
@@ -0,0 +1,21 @@
+$if(titleblock)$
+$titleblock$
+
+$endif$
+$for(header-includes)$
+$header-includes$
+
+$endfor$
+$for(include-before)$
+$include-before$
+
+$endfor$
+$if(toc)$
+$table-of-contents$
+
+$endif$
+$body$
+$for(include-after)$
+
+$include-after$
+$endfor$
diff --git a/data/templates/default.revealjs b/data/templates/default.revealjs
index 203983522..e1ca8b824 100644
--- a/data/templates/default.revealjs
+++ b/data/templates/default.revealjs
@@ -19,6 +19,9 @@ $endif$
<link rel="stylesheet" href="$revealjs-url$/dist/reset.css">
<link rel="stylesheet" href="$revealjs-url$/dist/reveal.css">
<style>
+ .reveal .sourceCode { /* see #7635 */
+ overflow: visible;
+ }
$styles.html()$
</style>
$if(theme)$
@@ -134,7 +137,7 @@ $endif$
// Disables the default reveal.js slide layout (scaling and centering)
// so that you can use custom CSS layout
- disableLayout: false,
+ disableLayout: $disableLayout$,
// Vertical centering of slides
center: $center$,
diff --git a/data/templates/default.rtf b/data/templates/default.rtf
index a7f79376d..10f596518 100644
--- a/data/templates/default.rtf
+++ b/data/templates/default.rtf
@@ -1,4 +1,4 @@
-{\rtf1\ansi\deff0{\fonttbl{\f0 \fswiss Helvetica;}{\f1 Courier;}}
+{\rtf1\ansi\deff0{\fonttbl{\f0 \fswiss Helvetica;}{\f1 \fmodern Courier;}}
{\colortbl;\red255\green0\blue0;\red0\green0\blue255;}
\widowctrl\hyphauto
$for(header-includes)$