diff options
Diffstat (limited to 'src/Text')
84 files changed, 1068 insertions, 151 deletions
| diff --git a/src/Text/Pandoc.hs b/src/Text/Pandoc.hs index f3301d140..e49fef3b5 100644 --- a/src/Text/Pandoc.hs +++ b/src/Text/Pandoc.hs @@ -150,7 +150,6 @@ import Text.Pandoc.Writers.RST  import Text.Pandoc.Writers.LaTeX  import Text.Pandoc.Writers.ConTeXt  import Text.Pandoc.Writers.Texinfo -import Prelude  import Text.Pandoc.Writers.HTML  import Text.Pandoc.Writers.ODT  import Text.Pandoc.Writers.Docx diff --git a/src/Text/Pandoc/Asciify.hs b/src/Text/Pandoc/Asciify.hs index a11809a00..c183458e4 100644 --- a/src/Text/Pandoc/Asciify.hs +++ b/src/Text/Pandoc/Asciify.hs @@ -30,7 +30,6 @@ ascii equivalents (used in constructing HTML identifiers).  -}  module Text.Pandoc.Asciify (toAsciiChar)  where -import Prelude  import qualified Data.Map as M  import Data.Char (isAscii) diff --git a/src/Text/Pandoc/CSS.hs b/src/Text/Pandoc/CSS.hs index ad0d0636a..9d0c84243 100644 --- a/src/Text/Pandoc/CSS.hs +++ b/src/Text/Pandoc/CSS.hs @@ -3,7 +3,6 @@ module Text.Pandoc.CSS ( foldOrElse,                         )  where -import Prelude  import Text.Pandoc.Shared (trim)  import Text.Parsec  import Text.Parsec.String diff --git a/src/Text/Pandoc/Compat/Directory.hs b/src/Text/Pandoc/Compat/Directory.hs index c8f3cc047..61dd5c525 100644 --- a/src/Text/Pandoc/Compat/Directory.hs +++ b/src/Text/Pandoc/Compat/Directory.hs @@ -5,6 +5,7 @@ module Text.Pandoc.Compat.Directory ( getModificationTime )  #if MIN_VERSION_directory(1,2,0)  import System.Directory +  #else  import qualified System.Directory as S  import Data.Time.Clock (UTCTime) diff --git a/src/Text/Pandoc/Compat/Except.hs b/src/Text/Pandoc/Compat/Except.hs index 5c1214f47..9ce7c0d36 100644 --- a/src/Text/Pandoc/Compat/Except.hs +++ b/src/Text/Pandoc/Compat/Except.hs @@ -9,7 +9,6 @@ module Text.Pandoc.Compat.Except ( ExceptT                                   , catchError )         where -import Prelude  #if MIN_VERSION_mtl(2,2,1)  import Control.Monad.Except diff --git a/src/Text/Pandoc/Compat/Monoid.hs b/src/Text/Pandoc/Compat/Monoid.hs new file mode 100644 index 000000000..4daceb8e1 --- /dev/null +++ b/src/Text/Pandoc/Compat/Monoid.hs @@ -0,0 +1,17 @@ +{-# LANGUAGE CPP #-} +module Text.Pandoc.Compat.Monoid ( (<>) ) +       where + +#if MIN_VERSION_base(4,5,0) +import Data.Monoid ((<>)) + +#else +import Data.Monoid + +infixr 6 <> + +--- | An infix synonym for 'mappend'. +(<>) :: Monoid m => m -> m -> m +(<>) = mappend +{-# INLINE (<>) #-} +#endif diff --git a/src/Text/Pandoc/Compat/TagSoupEntity.hs b/src/Text/Pandoc/Compat/TagSoupEntity.hs index 30889e915..80985aef9 100644 --- a/src/Text/Pandoc/Compat/TagSoupEntity.hs +++ b/src/Text/Pandoc/Compat/TagSoupEntity.hs @@ -2,7 +2,6 @@  module Text.Pandoc.Compat.TagSoupEntity (lookupEntity                            ) where -import Prelude  import qualified Text.HTML.TagSoup.Entity as TE  lookupEntity :: String -> Maybe Char diff --git a/src/Text/Pandoc/Emoji.hs b/src/Text/Pandoc/Emoji.hs new file mode 100644 index 000000000..c98b06fa1 --- /dev/null +++ b/src/Text/Pandoc/Emoji.hs @@ -0,0 +1,905 @@ +{- +Copyright (C) 2015 John MacFarlane <jgm@berkeley.edu> + +This program is free software; you can redistribute it and/or modify +it under the terms of the GNU General Public License as published by +the Free Software Foundation; either version 2 of the License, or +(at your option) any later version. + +This program is distributed in the hope that it will be useful, +but WITHOUT ANY WARRANTY; without even the implied warranty of +MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the +GNU General Public License for more details. + +You should have received a copy of the GNU General Public License +along with this program; if not, write to the Free Software +Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA +-} + +{- | +   Module      : Text.Pandoc.Emoji +   Copyright   : Copyright (C) 2015 John MacFarlane +   License     : GNU GPL, version 2 or above + +   Maintainer  : John MacFarlane <jgm@berkeley.edu> +   Stability   : alpha +   Portability : portable + +Emoji symbol lookup from canonical string identifier. +-} +module Text.Pandoc.Emoji ( emojis ) where +import qualified Data.Map as M + +emojis :: M.Map String String +emojis = M.fromList +  [ ("100", "\x1f4af") +  , ("1234", "\x1f522") +  , ("smile", "\x1f604") +  , ("smiley", "\x1f603") +  , ("grinning", "\x1f600") +  , ("blush", "\x1f60a") +  , ("relaxed", "\x263a\fe0f") +  , ("wink", "\x1f609") +  , ("heart_eyes", "\x1f60d") +  , ("kissing_heart", "\x1f618") +  , ("kissing_closed_eyes", "\x1f61a") +  , ("kissing", "\x1f617") +  , ("kissing_smiling_eyes", "\x1f619") +  , ("stuck_out_tongue_winking_eye", "\x1f61c") +  , ("stuck_out_tongue_closed_eyes", "\x1f61d") +  , ("stuck_out_tongue", "\x1f61b") +  , ("flushed", "\x1f633") +  , ("grin", "\x1f601") +  , ("pensive", "\x1f614") +  , ("relieved", "\x1f60c") +  , ("unamused", "\x1f612") +  , ("disappointed", "\x1f61e") +  , ("persevere", "\x1f623") +  , ("cry", "\x1f622") +  , ("joy", "\x1f602") +  , ("sob", "\x1f62d") +  , ("sleepy", "\x1f62a") +  , ("disappointed_relieved", "\x1f625") +  , ("cold_sweat", "\x1f630") +  , ("sweat_smile", "\x1f605") +  , ("sweat", "\x1f613") +  , ("weary", "\x1f629") +  , ("tired_face", "\x1f62b") +  , ("fearful", "\x1f628") +  , ("scream", "\x1f631") +  , ("angry", "\x1f620") +  , ("rage", "\x1f621") +  , ("triumph", "\x1f624") +  , ("confounded", "\x1f616") +  , ("laughing", "\x1f606") +  , ("satisfied", "\x1f606") +  , ("yum", "\x1f60b") +  , ("mask", "\x1f637") +  , ("sunglasses", "\x1f60e") +  , ("sleeping", "\x1f634") +  , ("dizzy_face", "\x1f635") +  , ("astonished", "\x1f632") +  , ("worried", "\x1f61f") +  , ("frowning", "\x1f626") +  , ("anguished", "\x1f627") +  , ("smiling_imp", "\x1f608") +  , ("imp", "\x1f47f") +  , ("open_mouth", "\x1f62e") +  , ("grimacing", "\x1f62c") +  , ("neutral_face", "\x1f610") +  , ("confused", "\x1f615") +  , ("hushed", "\x1f62f") +  , ("no_mouth", "\x1f636") +  , ("innocent", "\x1f607") +  , ("smirk", "\x1f60f") +  , ("expressionless", "\x1f611") +  , ("man_with_gua_pi_mao", "\x1f472") +  , ("man_with_turban", "\x1f473") +  , ("cop", "\x1f46e") +  , ("construction_worker", "\x1f477") +  , ("guardsman", "\x1f482") +  , ("baby", "\x1f476") +  , ("boy", "\x1f466") +  , ("girl", "\x1f467") +  , ("man", "\x1f468") +  , ("woman", "\x1f469") +  , ("older_man", "\x1f474") +  , ("older_woman", "\x1f475") +  , ("person_with_blond_hair", "\x1f471") +  , ("angel", "\x1f47c") +  , ("princess", "\x1f478") +  , ("smiley_cat", "\x1f63a") +  , ("smile_cat", "\x1f638") +  , ("heart_eyes_cat", "\x1f63b") +  , ("kissing_cat", "\x1f63d") +  , ("smirk_cat", "\x1f63c") +  , ("scream_cat", "\x1f640") +  , ("crying_cat_face", "\x1f63f") +  , ("joy_cat", "\x1f639") +  , ("pouting_cat", "\x1f63e") +  , ("japanese_ogre", "\x1f479") +  , ("japanese_goblin", "\x1f47a") +  , ("see_no_evil", "\x1f648") +  , ("hear_no_evil", "\x1f649") +  , ("speak_no_evil", "\x1f64a") +  , ("skull", "\x1f480") +  , ("alien", "\x1f47d") +  , ("hankey", "\x1f4a9") +  , ("poop", "\x1f4a9") +  , ("shit", "\x1f4a9") +  , ("fire", "\x1f525") +  , ("sparkles", "\x2728") +  , ("star2", "\x1f31f") +  , ("dizzy", "\x1f4ab") +  , ("boom", "\x1f4a5") +  , ("collision", "\x1f4a5") +  , ("anger", "\x1f4a2") +  , ("sweat_drops", "\x1f4a6") +  , ("droplet", "\x1f4a7") +  , ("zzz", "\x1f4a4") +  , ("dash", "\x1f4a8") +  , ("ear", "\x1f442") +  , ("eyes", "\x1f440") +  , ("nose", "\x1f443") +  , ("tongue", "\x1f445") +  , ("lips", "\x1f444") +  , ("+1", "\x1f44d") +  , ("thumbsup", "\x1f44d") +  , ("-1", "\x1f44e") +  , ("thumbsdown", "\x1f44e") +  , ("ok_hand", "\x1f44c") +  , ("facepunch", "\x1f44a") +  , ("punch", "\x1f44a") +  , ("fist", "\x270a") +  , ("v", "\x270c\fe0f") +  , ("wave", "\x1f44b") +  , ("hand", "\x270b") +  , ("raised_hand", "\x270b") +  , ("open_hands", "\x1f450") +  , ("point_up_2", "\x1f446") +  , ("point_down", "\x1f447") +  , ("point_right", "\x1f449") +  , ("point_left", "\x1f448") +  , ("raised_hands", "\x1f64c") +  , ("pray", "\x1f64f") +  , ("point_up", "\x261d\fe0f") +  , ("clap", "\x1f44f") +  , ("muscle", "\x1f4aa") +  , ("walking", "\x1f6b6") +  , ("runner", "\x1f3c3") +  , ("running", "\x1f3c3") +  , ("dancer", "\x1f483") +  , ("couple", "\x1f46b") +  , ("family", "\x1f46a") +  , ("two_men_holding_hands", "\x1f46c") +  , ("two_women_holding_hands", "\x1f46d") +  , ("couplekiss", "\x1f48f") +  , ("couple_with_heart", "\x1f491") +  , ("dancers", "\x1f46f") +  , ("ok_woman", "\x1f646") +  , ("no_good", "\x1f645") +  , ("information_desk_person", "\x1f481") +  , ("raising_hand", "\x1f64b") +  , ("massage", "\x1f486") +  , ("haircut", "\x1f487") +  , ("nail_care", "\x1f485") +  , ("bride_with_veil", "\x1f470") +  , ("person_with_pouting_face", "\x1f64e") +  , ("person_frowning", "\x1f64d") +  , ("bow", "\x1f647") +  , ("tophat", "\x1f3a9") +  , ("crown", "\x1f451") +  , ("womans_hat", "\x1f452") +  , ("athletic_shoe", "\x1f45f") +  , ("mans_shoe", "\x1f45e") +  , ("shoe", "\x1f45e") +  , ("sandal", "\x1f461") +  , ("high_heel", "\x1f460") +  , ("boot", "\x1f462") +  , ("shirt", "\x1f455") +  , ("tshirt", "\x1f455") +  , ("necktie", "\x1f454") +  , ("womans_clothes", "\x1f45a") +  , ("dress", "\x1f457") +  , ("running_shirt_with_sash", "\x1f3bd") +  , ("jeans", "\x1f456") +  , ("kimono", "\x1f458") +  , ("bikini", "\x1f459") +  , ("briefcase", "\x1f4bc") +  , ("handbag", "\x1f45c") +  , ("pouch", "\x1f45d") +  , ("purse", "\x1f45b") +  , ("eyeglasses", "\x1f453") +  , ("ribbon", "\x1f380") +  , ("closed_umbrella", "\x1f302") +  , ("lipstick", "\x1f484") +  , ("yellow_heart", "\x1f49b") +  , ("blue_heart", "\x1f499") +  , ("purple_heart", "\x1f49c") +  , ("green_heart", "\x1f49a") +  , ("heart", "\x2764\fe0f") +  , ("broken_heart", "\x1f494") +  , ("heartpulse", "\x1f497") +  , ("heartbeat", "\x1f493") +  , ("two_hearts", "\x1f495") +  , ("sparkling_heart", "\x1f496") +  , ("revolving_hearts", "\x1f49e") +  , ("cupid", "\x1f498") +  , ("love_letter", "\x1f48c") +  , ("kiss", "\x1f48b") +  , ("ring", "\x1f48d") +  , ("gem", "\x1f48e") +  , ("bust_in_silhouette", "\x1f464") +  , ("busts_in_silhouette", "\x1f465") +  , ("speech_balloon", "\x1f4ac") +  , ("footprints", "\x1f463") +  , ("thought_balloon", "\x1f4ad") +  , ("dog", "\x1f436") +  , ("wolf", "\x1f43a") +  , ("cat", "\x1f431") +  , ("mouse", "\x1f42d") +  , ("hamster", "\x1f439") +  , ("rabbit", "\x1f430") +  , ("frog", "\x1f438") +  , ("tiger", "\x1f42f") +  , ("koala", "\x1f428") +  , ("bear", "\x1f43b") +  , ("pig", "\x1f437") +  , ("pig_nose", "\x1f43d") +  , ("cow", "\x1f42e") +  , ("boar", "\x1f417") +  , ("monkey_face", "\x1f435") +  , ("monkey", "\x1f412") +  , ("horse", "\x1f434") +  , ("sheep", "\x1f411") +  , ("elephant", "\x1f418") +  , ("panda_face", "\x1f43c") +  , ("penguin", "\x1f427") +  , ("bird", "\x1f426") +  , ("baby_chick", "\x1f424") +  , ("hatched_chick", "\x1f425") +  , ("hatching_chick", "\x1f423") +  , ("chicken", "\x1f414") +  , ("snake", "\x1f40d") +  , ("turtle", "\x1f422") +  , ("bug", "\x1f41b") +  , ("bee", "\x1f41d") +  , ("honeybee", "\x1f41d") +  , ("ant", "\x1f41c") +  , ("beetle", "\x1f41e") +  , ("snail", "\x1f40c") +  , ("octopus", "\x1f419") +  , ("shell", "\x1f41a") +  , ("tropical_fish", "\x1f420") +  , ("fish", "\x1f41f") +  , ("dolphin", "\x1f42c") +  , ("flipper", "\x1f42c") +  , ("whale", "\x1f433") +  , ("whale2", "\x1f40b") +  , ("cow2", "\x1f404") +  , ("ram", "\x1f40f") +  , ("rat", "\x1f400") +  , ("water_buffalo", "\x1f403") +  , ("tiger2", "\x1f405") +  , ("rabbit2", "\x1f407") +  , ("dragon", "\x1f409") +  , ("racehorse", "\x1f40e") +  , ("goat", "\x1f410") +  , ("rooster", "\x1f413") +  , ("dog2", "\x1f415") +  , ("pig2", "\x1f416") +  , ("mouse2", "\x1f401") +  , ("ox", "\x1f402") +  , ("dragon_face", "\x1f432") +  , ("blowfish", "\x1f421") +  , ("crocodile", "\x1f40a") +  , ("camel", "\x1f42b") +  , ("dromedary_camel", "\x1f42a") +  , ("leopard", "\x1f406") +  , ("cat2", "\x1f408") +  , ("poodle", "\x1f429") +  , ("feet", "\x1f43e") +  , ("paw_prints", "\x1f43e") +  , ("bouquet", "\x1f490") +  , ("cherry_blossom", "\x1f338") +  , ("tulip", "\x1f337") +  , ("four_leaf_clover", "\x1f340") +  , ("rose", "\x1f339") +  , ("sunflower", "\x1f33b") +  , ("hibiscus", "\x1f33a") +  , ("maple_leaf", "\x1f341") +  , ("leaves", "\x1f343") +  , ("fallen_leaf", "\x1f342") +  , ("herb", "\x1f33f") +  , ("ear_of_rice", "\x1f33e") +  , ("mushroom", "\x1f344") +  , ("cactus", "\x1f335") +  , ("palm_tree", "\x1f334") +  , ("evergreen_tree", "\x1f332") +  , ("deciduous_tree", "\x1f333") +  , ("chestnut", "\x1f330") +  , ("seedling", "\x1f331") +  , ("blossom", "\x1f33c") +  , ("globe_with_meridians", "\x1f310") +  , ("sun_with_face", "\x1f31e") +  , ("full_moon_with_face", "\x1f31d") +  , ("new_moon_with_face", "\x1f31a") +  , ("new_moon", "\x1f311") +  , ("waxing_crescent_moon", "\x1f312") +  , ("first_quarter_moon", "\x1f313") +  , ("moon", "\x1f314") +  , ("waxing_gibbous_moon", "\x1f314") +  , ("full_moon", "\x1f315") +  , ("waning_gibbous_moon", "\x1f316") +  , ("last_quarter_moon", "\x1f317") +  , ("waning_crescent_moon", "\x1f318") +  , ("last_quarter_moon_with_face", "\x1f31c") +  , ("first_quarter_moon_with_face", "\x1f31b") +  , ("crescent_moon", "\x1f319") +  , ("earth_africa", "\x1f30d") +  , ("earth_americas", "\x1f30e") +  , ("earth_asia", "\x1f30f") +  , ("volcano", "\x1f30b") +  , ("milky_way", "\x1f30c") +  , ("stars", "\x1f320") +  , ("star", "\x2b50") +  , ("sunny", "\x2600\fe0f") +  , ("partly_sunny", "\x26c5") +  , ("cloud", "\x2601\fe0f") +  , ("zap", "\x26a1") +  , ("umbrella", "\x2614") +  , ("snowflake", "\x2744\fe0f") +  , ("snowman", "\x26c4") +  , ("cyclone", "\x1f300") +  , ("foggy", "\x1f301") +  , ("rainbow", "\x1f308") +  , ("ocean", "\x1f30a") +  , ("bamboo", "\x1f38d") +  , ("gift_heart", "\x1f49d") +  , ("dolls", "\x1f38e") +  , ("school_satchel", "\x1f392") +  , ("mortar_board", "\x1f393") +  , ("flags", "\x1f38f") +  , ("fireworks", "\x1f386") +  , ("sparkler", "\x1f387") +  , ("wind_chime", "\x1f390") +  , ("rice_scene", "\x1f391") +  , ("jack_o_lantern", "\x1f383") +  , ("ghost", "\x1f47b") +  , ("santa", "\x1f385") +  , ("christmas_tree", "\x1f384") +  , ("gift", "\x1f381") +  , ("tanabata_tree", "\x1f38b") +  , ("tada", "\x1f389") +  , ("confetti_ball", "\x1f38a") +  , ("balloon", "\x1f388") +  , ("crossed_flags", "\x1f38c") +  , ("crystal_ball", "\x1f52e") +  , ("movie_camera", "\x1f3a5") +  , ("camera", "\x1f4f7") +  , ("video_camera", "\x1f4f9") +  , ("vhs", "\x1f4fc") +  , ("cd", "\x1f4bf") +  , ("dvd", "\x1f4c0") +  , ("minidisc", "\x1f4bd") +  , ("floppy_disk", "\x1f4be") +  , ("computer", "\x1f4bb") +  , ("iphone", "\x1f4f1") +  , ("phone", "\x260e\fe0f") +  , ("telephone", "\x260e\fe0f") +  , ("telephone_receiver", "\x1f4de") +  , ("pager", "\x1f4df") +  , ("fax", "\x1f4e0") +  , ("satellite", "\x1f4e1") +  , ("tv", "\x1f4fa") +  , ("radio", "\x1f4fb") +  , ("loud_sound", "\x1f50a") +  , ("sound", "\x1f509") +  , ("speaker", "\x1f508") +  , ("mute", "\x1f507") +  , ("bell", "\x1f514") +  , ("no_bell", "\x1f515") +  , ("loudspeaker", "\x1f4e2") +  , ("mega", "\x1f4e3") +  , ("hourglass_flowing_sand", "\x23f3") +  , ("hourglass", "\x231b") +  , ("alarm_clock", "\x23f0") +  , ("watch", "\x231a") +  , ("unlock", "\x1f513") +  , ("lock", "\x1f512") +  , ("lock_with_ink_pen", "\x1f50f") +  , ("closed_lock_with_key", "\x1f510") +  , ("key", "\x1f511") +  , ("mag_right", "\x1f50e") +  , ("bulb", "\x1f4a1") +  , ("flashlight", "\x1f526") +  , ("high_brightness", "\x1f506") +  , ("low_brightness", "\x1f505") +  , ("electric_plug", "\x1f50c") +  , ("battery", "\x1f50b") +  , ("mag", "\x1f50d") +  , ("bathtub", "\x1f6c1") +  , ("bath", "\x1f6c0") +  , ("shower", "\x1f6bf") +  , ("toilet", "\x1f6bd") +  , ("wrench", "\x1f527") +  , ("nut_and_bolt", "\x1f529") +  , ("hammer", "\x1f528") +  , ("door", "\x1f6aa") +  , ("smoking", "\x1f6ac") +  , ("bomb", "\x1f4a3") +  , ("gun", "\x1f52b") +  , ("hocho", "\x1f52a") +  , ("knife", "\x1f52a") +  , ("pill", "\x1f48a") +  , ("syringe", "\x1f489") +  , ("moneybag", "\x1f4b0") +  , ("yen", "\x1f4b4") +  , ("dollar", "\x1f4b5") +  , ("pound", "\x1f4b7") +  , ("euro", "\x1f4b6") +  , ("credit_card", "\x1f4b3") +  , ("money_with_wings", "\x1f4b8") +  , ("calling", "\x1f4f2") +  , ("e-mail", "\x1f4e7") +  , ("inbox_tray", "\x1f4e5") +  , ("outbox_tray", "\x1f4e4") +  , ("email", "\x2709\fe0f") +  , ("envelope", "\x2709\fe0f") +  , ("envelope_with_arrow", "\x1f4e9") +  , ("incoming_envelope", "\x1f4e8") +  , ("postal_horn", "\x1f4ef") +  , ("mailbox", "\x1f4eb") +  , ("mailbox_closed", "\x1f4ea") +  , ("mailbox_with_mail", "\x1f4ec") +  , ("mailbox_with_no_mail", "\x1f4ed") +  , ("postbox", "\x1f4ee") +  , ("package", "\x1f4e6") +  , ("memo", "\x1f4dd") +  , ("pencil", "\x1f4dd") +  , ("page_facing_up", "\x1f4c4") +  , ("page_with_curl", "\x1f4c3") +  , ("bookmark_tabs", "\x1f4d1") +  , ("bar_chart", "\x1f4ca") +  , ("chart_with_upwards_trend", "\x1f4c8") +  , ("chart_with_downwards_trend", "\x1f4c9") +  , ("scroll", "\x1f4dc") +  , ("clipboard", "\x1f4cb") +  , ("date", "\x1f4c5") +  , ("calendar", "\x1f4c6") +  , ("card_index", "\x1f4c7") +  , ("file_folder", "\x1f4c1") +  , ("open_file_folder", "\x1f4c2") +  , ("scissors", "\x2702\fe0f") +  , ("pushpin", "\x1f4cc") +  , ("paperclip", "\x1f4ce") +  , ("black_nib", "\x2712\fe0f") +  , ("pencil2", "\x270f\fe0f") +  , ("straight_ruler", "\x1f4cf") +  , ("triangular_ruler", "\x1f4d0") +  , ("closed_book", "\x1f4d5") +  , ("green_book", "\x1f4d7") +  , ("blue_book", "\x1f4d8") +  , ("orange_book", "\x1f4d9") +  , ("notebook", "\x1f4d3") +  , ("notebook_with_decorative_cover", "\x1f4d4") +  , ("ledger", "\x1f4d2") +  , ("books", "\x1f4da") +  , ("book", "\x1f4d6") +  , ("open_book", "\x1f4d6") +  , ("bookmark", "\x1f516") +  , ("name_badge", "\x1f4db") +  , ("microscope", "\x1f52c") +  , ("telescope", "\x1f52d") +  , ("newspaper", "\x1f4f0") +  , ("art", "\x1f3a8") +  , ("clapper", "\x1f3ac") +  , ("microphone", "\x1f3a4") +  , ("headphones", "\x1f3a7") +  , ("musical_score", "\x1f3bc") +  , ("musical_note", "\x1f3b5") +  , ("notes", "\x1f3b6") +  , ("musical_keyboard", "\x1f3b9") +  , ("violin", "\x1f3bb") +  , ("trumpet", "\x1f3ba") +  , ("saxophone", "\x1f3b7") +  , ("guitar", "\x1f3b8") +  , ("space_invader", "\x1f47e") +  , ("video_game", "\x1f3ae") +  , ("black_joker", "\x1f0cf") +  , ("flower_playing_cards", "\x1f3b4") +  , ("mahjong", "\x1f004") +  , ("game_die", "\x1f3b2") +  , ("dart", "\x1f3af") +  , ("football", "\x1f3c8") +  , ("basketball", "\x1f3c0") +  , ("soccer", "\x26bd") +  , ("baseball", "\x26be\fe0f") +  , ("tennis", "\x1f3be") +  , ("8ball", "\x1f3b1") +  , ("rugby_football", "\x1f3c9") +  , ("bowling", "\x1f3b3") +  , ("golf", "\x26f3") +  , ("mountain_bicyclist", "\x1f6b5") +  , ("bicyclist", "\x1f6b4") +  , ("checkered_flag", "\x1f3c1") +  , ("horse_racing", "\x1f3c7") +  , ("trophy", "\x1f3c6") +  , ("ski", "\x1f3bf") +  , ("snowboarder", "\x1f3c2") +  , ("swimmer", "\x1f3ca") +  , ("surfer", "\x1f3c4") +  , ("fishing_pole_and_fish", "\x1f3a3") +  , ("coffee", "\x2615") +  , ("tea", "\x1f375") +  , ("sake", "\x1f376") +  , ("baby_bottle", "\x1f37c") +  , ("beer", "\x1f37a") +  , ("beers", "\x1f37b") +  , ("cocktail", "\x1f378") +  , ("tropical_drink", "\x1f379") +  , ("wine_glass", "\x1f377") +  , ("fork_and_knife", "\x1f374") +  , ("pizza", "\x1f355") +  , ("hamburger", "\x1f354") +  , ("fries", "\x1f35f") +  , ("poultry_leg", "\x1f357") +  , ("meat_on_bone", "\x1f356") +  , ("spaghetti", "\x1f35d") +  , ("curry", "\x1f35b") +  , ("fried_shrimp", "\x1f364") +  , ("bento", "\x1f371") +  , ("sushi", "\x1f363") +  , ("fish_cake", "\x1f365") +  , ("rice_ball", "\x1f359") +  , ("rice_cracker", "\x1f358") +  , ("rice", "\x1f35a") +  , ("ramen", "\x1f35c") +  , ("stew", "\x1f372") +  , ("oden", "\x1f362") +  , ("dango", "\x1f361") +  , ("egg", "\x1f373") +  , ("bread", "\x1f35e") +  , ("doughnut", "\x1f369") +  , ("custard", "\x1f36e") +  , ("icecream", "\x1f366") +  , ("ice_cream", "\x1f368") +  , ("shaved_ice", "\x1f367") +  , ("birthday", "\x1f382") +  , ("cake", "\x1f370") +  , ("cookie", "\x1f36a") +  , ("chocolate_bar", "\x1f36b") +  , ("candy", "\x1f36c") +  , ("lollipop", "\x1f36d") +  , ("honey_pot", "\x1f36f") +  , ("apple", "\x1f34e") +  , ("green_apple", "\x1f34f") +  , ("tangerine", "\x1f34a") +  , ("lemon", "\x1f34b") +  , ("cherries", "\x1f352") +  , ("grapes", "\x1f347") +  , ("watermelon", "\x1f349") +  , ("strawberry", "\x1f353") +  , ("peach", "\x1f351") +  , ("melon", "\x1f348") +  , ("banana", "\x1f34c") +  , ("pear", "\x1f350") +  , ("pineapple", "\x1f34d") +  , ("sweet_potato", "\x1f360") +  , ("eggplant", "\x1f346") +  , ("tomato", "\x1f345") +  , ("corn", "\x1f33d") +  , ("house", "\x1f3e0") +  , ("house_with_garden", "\x1f3e1") +  , ("school", "\x1f3eb") +  , ("office", "\x1f3e2") +  , ("post_office", "\x1f3e3") +  , ("hospital", "\x1f3e5") +  , ("bank", "\x1f3e6") +  , ("convenience_store", "\x1f3ea") +  , ("love_hotel", "\x1f3e9") +  , ("hotel", "\x1f3e8") +  , ("wedding", "\x1f492") +  , ("church", "\x26ea") +  , ("department_store", "\x1f3ec") +  , ("european_post_office", "\x1f3e4") +  , ("city_sunrise", "\x1f307") +  , ("city_sunset", "\x1f306") +  , ("japanese_castle", "\x1f3ef") +  , ("european_castle", "\x1f3f0") +  , ("tent", "\x26fa") +  , ("factory", "\x1f3ed") +  , ("tokyo_tower", "\x1f5fc") +  , ("japan", "\x1f5fe") +  , ("mount_fuji", "\x1f5fb") +  , ("sunrise_over_mountains", "\x1f304") +  , ("sunrise", "\x1f305") +  , ("night_with_stars", "\x1f303") +  , ("statue_of_liberty", "\x1f5fd") +  , ("bridge_at_night", "\x1f309") +  , ("carousel_horse", "\x1f3a0") +  , ("ferris_wheel", "\x1f3a1") +  , ("fountain", "\x26f2") +  , ("roller_coaster", "\x1f3a2") +  , ("ship", "\x1f6a2") +  , ("boat", "\x26f5") +  , ("sailboat", "\x26f5") +  , ("speedboat", "\x1f6a4") +  , ("rowboat", "\x1f6a3") +  , ("anchor", "\x2693") +  , ("rocket", "\x1f680") +  , ("airplane", "\x2708\fe0f") +  , ("seat", "\x1f4ba") +  , ("helicopter", "\x1f681") +  , ("steam_locomotive", "\x1f682") +  , ("tram", "\x1f68a") +  , ("station", "\x1f689") +  , ("mountain_railway", "\x1f69e") +  , ("train2", "\x1f686") +  , ("bullettrain_side", "\x1f684") +  , ("bullettrain_front", "\x1f685") +  , ("light_rail", "\x1f688") +  , ("metro", "\x1f687") +  , ("monorail", "\x1f69d") +  , ("train", "\x1f68b") +  , ("railway_car", "\x1f683") +  , ("trolleybus", "\x1f68e") +  , ("bus", "\x1f68c") +  , ("oncoming_bus", "\x1f68d") +  , ("blue_car", "\x1f699") +  , ("oncoming_automobile", "\x1f698") +  , ("car", "\x1f697") +  , ("red_car", "\x1f697") +  , ("taxi", "\x1f695") +  , ("oncoming_taxi", "\x1f696") +  , ("articulated_lorry", "\x1f69b") +  , ("truck", "\x1f69a") +  , ("rotating_light", "\x1f6a8") +  , ("police_car", "\x1f693") +  , ("oncoming_police_car", "\x1f694") +  , ("fire_engine", "\x1f692") +  , ("ambulance", "\x1f691") +  , ("minibus", "\x1f690") +  , ("bike", "\x1f6b2") +  , ("aerial_tramway", "\x1f6a1") +  , ("suspension_railway", "\x1f69f") +  , ("mountain_cableway", "\x1f6a0") +  , ("tractor", "\x1f69c") +  , ("barber", "\x1f488") +  , ("busstop", "\x1f68f") +  , ("ticket", "\x1f3ab") +  , ("vertical_traffic_light", "\x1f6a6") +  , ("traffic_light", "\x1f6a5") +  , ("warning", "\x26a0\fe0f") +  , ("construction", "\x1f6a7") +  , ("beginner", "\x1f530") +  , ("fuelpump", "\x26fd") +  , ("izakaya_lantern", "\x1f3ee") +  , ("lantern", "\x1f3ee") +  , ("slot_machine", "\x1f3b0") +  , ("hotsprings", "\x2668\fe0f") +  , ("moyai", "\x1f5ff") +  , ("circus_tent", "\x1f3aa") +  , ("performing_arts", "\x1f3ad") +  , ("round_pushpin", "\x1f4cd") +  , ("triangular_flag_on_post", "\x1f6a9") +  , ("jp", "\x1f1ef\1f1f5") +  , ("kr", "\x1f1f0\1f1f7") +  , ("de", "\x1f1e9\1f1ea") +  , ("cn", "\x1f1e8\1f1f3") +  , ("us", "\x1f1fa\1f1f8") +  , ("fr", "\x1f1eb\1f1f7") +  , ("es", "\x1f1ea\1f1f8") +  , ("it", "\x1f1ee\1f1f9") +  , ("ru", "\x1f1f7\1f1fa") +  , ("gb", "\x1f1ec\1f1e7") +  , ("uk", "\x1f1ec\1f1e7") +  , ("one", "1\fe0f\20e3") +  , ("two", "2\fe0f\20e3") +  , ("three", "3\fe0f\20e3") +  , ("four", "4\fe0f\20e3") +  , ("five", "5\fe0f\20e3") +  , ("six", "6\fe0f\20e3") +  , ("seven", "7\fe0f\20e3") +  , ("eight", "8\fe0f\20e3") +  , ("nine", "9\fe0f\20e3") +  , ("zero", "0\fe0f\20e3") +  , ("keycap_ten", "\x1f51f") +  , ("hash", "#\fe0f\20e3") +  , ("symbols", "\x1f523") +  , ("arrow_up", "\x2b06\fe0f") +  , ("arrow_down", "\x2b07\fe0f") +  , ("arrow_left", "\x2b05\fe0f") +  , ("arrow_right", "\x27a1\fe0f") +  , ("capital_abcd", "\x1f520") +  , ("abcd", "\x1f521") +  , ("abc", "\x1f524") +  , ("arrow_upper_right", "\x2197\fe0f") +  , ("arrow_upper_left", "\x2196\fe0f") +  , ("arrow_lower_right", "\x2198\fe0f") +  , ("arrow_lower_left", "\x2199\fe0f") +  , ("left_right_arrow", "\x2194\fe0f") +  , ("arrow_up_down", "\x2195\fe0f") +  , ("arrows_counterclockwise", "\x1f504") +  , ("arrow_backward", "\x25c0\fe0f") +  , ("arrow_forward", "\x25b6\fe0f") +  , ("arrow_up_small", "\x1f53c") +  , ("arrow_down_small", "\x1f53d") +  , ("leftwards_arrow_with_hook", "\x21a9\fe0f") +  , ("arrow_right_hook", "\x21aa\fe0f") +  , ("information_source", "\x2139\fe0f") +  , ("rewind", "\x23ea") +  , ("fast_forward", "\x23e9") +  , ("arrow_double_up", "\x23eb") +  , ("arrow_double_down", "\x23ec") +  , ("arrow_heading_down", "\x2935\fe0f") +  , ("arrow_heading_up", "\x2934\fe0f") +  , ("ok", "\x1f197") +  , ("twisted_rightwards_arrows", "\x1f500") +  , ("repeat", "\x1f501") +  , ("repeat_one", "\x1f502") +  , ("new", "\x1f195") +  , ("up", "\x1f199") +  , ("cool", "\x1f192") +  , ("free", "\x1f193") +  , ("ng", "\x1f196") +  , ("signal_strength", "\x1f4f6") +  , ("cinema", "\x1f3a6") +  , ("koko", "\x1f201") +  , ("u6307", "\x1f22f") +  , ("u7a7a", "\x1f233") +  , ("u6e80", "\x1f235") +  , ("u5408", "\x1f234") +  , ("u7981", "\x1f232") +  , ("ideograph_advantage", "\x1f250") +  , ("u5272", "\x1f239") +  , ("u55b6", "\x1f23a") +  , ("u6709", "\x1f236") +  , ("u7121", "\x1f21a") +  , ("restroom", "\x1f6bb") +  , ("mens", "\x1f6b9") +  , ("womens", "\x1f6ba") +  , ("baby_symbol", "\x1f6bc") +  , ("wc", "\x1f6be") +  , ("potable_water", "\x1f6b0") +  , ("put_litter_in_its_place", "\x1f6ae") +  , ("parking", "\x1f17f\fe0f") +  , ("wheelchair", "\x267f") +  , ("no_smoking", "\x1f6ad") +  , ("u6708", "\x1f237\fe0f") +  , ("u7533", "\x1f238") +  , ("sa", "\x1f202\fe0f") +  , ("m", "\x24c2\fe0f") +  , ("passport_control", "\x1f6c2") +  , ("baggage_claim", "\x1f6c4") +  , ("left_luggage", "\x1f6c5") +  , ("customs", "\x1f6c3") +  , ("accept", "\x1f251") +  , ("secret", "\x3299\fe0f") +  , ("congratulations", "\x3297\fe0f") +  , ("cl", "\x1f191") +  , ("sos", "\x1f198") +  , ("id", "\x1f194") +  , ("no_entry_sign", "\x1f6ab") +  , ("underage", "\x1f51e") +  , ("no_mobile_phones", "\x1f4f5") +  , ("do_not_litter", "\x1f6af") +  , ("non-potable_water", "\x1f6b1") +  , ("no_bicycles", "\x1f6b3") +  , ("no_pedestrians", "\x1f6b7") +  , ("children_crossing", "\x1f6b8") +  , ("no_entry", "\x26d4") +  , ("eight_spoked_asterisk", "\x2733\fe0f") +  , ("sparkle", "\x2747\fe0f") +  , ("negative_squared_cross_mark", "\x274e") +  , ("white_check_mark", "\x2705") +  , ("eight_pointed_black_star", "\x2734\fe0f") +  , ("heart_decoration", "\x1f49f") +  , ("vs", "\x1f19a") +  , ("vibration_mode", "\x1f4f3") +  , ("mobile_phone_off", "\x1f4f4") +  , ("a", "\x1f170\fe0f") +  , ("b", "\x1f171\fe0f") +  , ("ab", "\x1f18e") +  , ("o2", "\x1f17e\fe0f") +  , ("diamond_shape_with_a_dot_inside", "\x1f4a0") +  , ("loop", "\x27bf") +  , ("recycle", "\x267b\fe0f") +  , ("aries", "\x2648") +  , ("taurus", "\x2649") +  , ("gemini", "\x264a") +  , ("cancer", "\x264b") +  , ("leo", "\x264c") +  , ("virgo", "\x264d") +  , ("libra", "\x264e") +  , ("scorpius", "\x264f") +  , ("sagittarius", "\x2650") +  , ("capricorn", "\x2651") +  , ("aquarius", "\x2652") +  , ("pisces", "\x2653") +  , ("ophiuchus", "\x26ce") +  , ("six_pointed_star", "\x1f52f") +  , ("atm", "\x1f3e7") +  , ("chart", "\x1f4b9") +  , ("heavy_dollar_sign", "\x1f4b2") +  , ("currency_exchange", "\x1f4b1") +  , ("copyright", "©\fe0f") +  , ("registered", "®\fe0f") +  , ("tm", "\x2122\fe0f") +  , ("x", "\x274c") +  , ("bangbang", "\x203c\fe0f") +  , ("interrobang", "\x2049\fe0f") +  , ("exclamation", "\x2757") +  , ("heavy_exclamation_mark", "\x2757") +  , ("question", "\x2753") +  , ("grey_exclamation", "\x2755") +  , ("grey_question", "\x2754") +  , ("o", "\x2b55") +  , ("top", "\x1f51d") +  , ("end", "\x1f51a") +  , ("back", "\x1f519") +  , ("on", "\x1f51b") +  , ("soon", "\x1f51c") +  , ("arrows_clockwise", "\x1f503") +  , ("clock12", "\x1f55b") +  , ("clock1230", "\x1f567") +  , ("clock1", "\x1f550") +  , ("clock130", "\x1f55c") +  , ("clock2", "\x1f551") +  , ("clock230", "\x1f55d") +  , ("clock3", "\x1f552") +  , ("clock330", "\x1f55e") +  , ("clock4", "\x1f553") +  , ("clock430", "\x1f55f") +  , ("clock5", "\x1f554") +  , ("clock530", "\x1f560") +  , ("clock6", "\x1f555") +  , ("clock7", "\x1f556") +  , ("clock8", "\x1f557") +  , ("clock9", "\x1f558") +  , ("clock10", "\x1f559") +  , ("clock11", "\x1f55a") +  , ("clock630", "\x1f561") +  , ("clock730", "\x1f562") +  , ("clock830", "\x1f563") +  , ("clock930", "\x1f564") +  , ("clock1030", "\x1f565") +  , ("clock1130", "\x1f566") +  , ("heavy_multiplication_x", "\x2716\fe0f") +  , ("heavy_plus_sign", "\x2795") +  , ("heavy_minus_sign", "\x2796") +  , ("heavy_division_sign", "\x2797") +  , ("spades", "\x2660\fe0f") +  , ("hearts", "\x2665\fe0f") +  , ("clubs", "\x2663\fe0f") +  , ("diamonds", "\x2666\fe0f") +  , ("white_flower", "\x1f4ae") +  , ("heavy_check_mark", "\x2714\fe0f") +  , ("ballot_box_with_check", "\x2611\fe0f") +  , ("radio_button", "\x1f518") +  , ("link", "\x1f517") +  , ("curly_loop", "\x27b0") +  , ("wavy_dash", "\x3030\fe0f") +  , ("part_alternation_mark", "\x303d\fe0f") +  , ("trident", "\x1f531") +  , ("black_medium_square", "\x25fc\fe0f") +  , ("white_medium_square", "\x25fb\fe0f") +  , ("black_medium_small_square", "\x25fe") +  , ("white_medium_small_square", "\x25fd") +  , ("black_small_square", "\x25aa\fe0f") +  , ("white_small_square", "\x25ab\fe0f") +  , ("small_red_triangle", "\x1f53a") +  , ("black_square_button", "\x1f532") +  , ("white_square_button", "\x1f533") +  , ("black_circle", "\x26ab") +  , ("white_circle", "\x26aa") +  , ("red_circle", "\x1f534") +  , ("large_blue_circle", "\x1f535") +  , ("small_red_triangle_down", "\x1f53b") +  , ("white_large_square", "\x2b1c") +  , ("black_large_square", "\x2b1b") +  , ("large_orange_diamond", "\x1f536") +  , ("large_blue_diamond", "\x1f537") +  , ("small_orange_diamond", "\x1f538") +  , ("small_blue_diamond", "\x1f539") +  ] diff --git a/src/Text/Pandoc/Error.hs b/src/Text/Pandoc/Error.hs index 04084055e..0a4e08175 100644 --- a/src/Text/Pandoc/Error.hs +++ b/src/Text/Pandoc/Error.hs @@ -31,7 +31,6 @@ during parsing.  -}  module Text.Pandoc.Error (PandocError(..), handleError) where -import Prelude  import Text.Parsec.Error  import Text.Parsec.Pos hiding (Line)  import Text.Pandoc.Compat.Except diff --git a/src/Text/Pandoc/Highlighting.hs b/src/Text/Pandoc/Highlighting.hs index 40e1ec8ae..d0b945d45 100644 --- a/src/Text/Pandoc/Highlighting.hs +++ b/src/Text/Pandoc/Highlighting.hs @@ -48,7 +48,6 @@ module Text.Pandoc.Highlighting ( languages                                  , fromListingsLanguage                                  , toListingsLanguage                                  ) where -import Prelude  import Text.Pandoc.Definition  import Text.Pandoc.Shared (safeRead)  import Text.Highlighting.Kate diff --git a/src/Text/Pandoc/ImageSize.hs b/src/Text/Pandoc/ImageSize.hs index 5b4593a4c..a38a9dcd1 100644 --- a/src/Text/Pandoc/ImageSize.hs +++ b/src/Text/Pandoc/ImageSize.hs @@ -31,7 +31,6 @@ Functions for determining the size of a PNG, JPEG, or GIF image.  -}  module Text.Pandoc.ImageSize ( ImageType(..), imageType, imageSize,                      sizeInPixels, sizeInPoints ) where -import Prelude  import Data.ByteString (ByteString, unpack)  import qualified Data.ByteString.Char8 as B  import qualified Data.ByteString.Lazy as BL diff --git a/src/Text/Pandoc/MIME.hs b/src/Text/Pandoc/MIME.hs index 926a98b53..6fd9ac373 100644 --- a/src/Text/Pandoc/MIME.hs +++ b/src/Text/Pandoc/MIME.hs @@ -29,7 +29,6 @@ Mime type lookup for ODT writer.  -}  module Text.Pandoc.MIME ( MimeType, getMimeType, getMimeTypeDef,                            extensionFromMimeType )where -import Prelude  import System.FilePath  import Data.Char ( toLower )  import Data.List (isPrefixOf, isSuffixOf) diff --git a/src/Text/Pandoc/MediaBag.hs b/src/Text/Pandoc/MediaBag.hs index 8f965c3d5..eea25fadf 100644 --- a/src/Text/Pandoc/MediaBag.hs +++ b/src/Text/Pandoc/MediaBag.hs @@ -36,7 +36,6 @@ module Text.Pandoc.MediaBag (                       mediaDirectory,                       extractMediaBag                       ) where -import Prelude  import System.FilePath  import qualified System.FilePath.Posix as Posix  import System.Directory (createDirectoryIfMissing) diff --git a/src/Text/Pandoc/Options.hs b/src/Text/Pandoc/Options.hs index a97c4179d..158303acd 100644 --- a/src/Text/Pandoc/Options.hs +++ b/src/Text/Pandoc/Options.hs @@ -1,4 +1,4 @@ -{-# LANGUAGE DeriveDataTypeable #-} +{-# LANGUAGE DeriveDataTypeable, DeriveGeneric #-}  {-  Copyright (C) 2012-2015 John MacFarlane <jgm@berkeley.edu> @@ -47,7 +47,6 @@ module Text.Pandoc.Options ( Extension(..)                             , def                             , isEnabled                             ) where -import Prelude  import Data.Set (Set)  import qualified Data.Set as Set  import Data.Default @@ -55,6 +54,7 @@ import Text.Pandoc.Highlighting (Style, pygments)  import Text.Pandoc.MediaBag (MediaBag)  import Data.Data (Data)  import Data.Typeable (Typeable) +import GHC.Generics (Generic)  -- | Individually selectable syntax extensions.  data Extension = @@ -106,6 +106,7 @@ data Extension =      | Ext_ignore_line_breaks  -- ^ Newlines in paragraphs are ignored      | Ext_literate_haskell    -- ^ Enable literate Haskell conventions      | Ext_abbreviations       -- ^ PHP markdown extra abbreviation definitions +    | Ext_emoji               -- ^ Support emoji like :smile:      | Ext_auto_identifiers    -- ^ Automatic identifiers for headers      | Ext_ascii_identifiers   -- ^ ascii-only identifiers for headers      | Ext_header_attributes   -- ^ Explicit header attributes {#id .class k=v} @@ -114,7 +115,7 @@ data Extension =      | Ext_line_blocks         -- ^ RST style line blocks      | Ext_epub_html_exts      -- ^ Recognise the EPUB extended version of HTML      | Ext_shortcut_reference_links -- ^ Shortcut reference links -    deriving (Show, Read, Enum, Eq, Ord, Bounded, Data, Typeable) +    deriving (Show, Read, Enum, Eq, Ord, Bounded, Data, Typeable, Generic)  pandocExtensions :: Set Extension  pandocExtensions = Set.fromList @@ -204,6 +205,7 @@ githubMarkdownExtensions = Set.fromList    , Ext_intraword_underscores    , Ext_strikeout    , Ext_hard_line_breaks +  , Ext_emoji    , Ext_lists_without_preceding_blankline    , Ext_shortcut_reference_links    ] @@ -257,7 +259,7 @@ data ReaderOptions = ReaderOptions{         , readerDefaultImageExtension :: String -- ^ Default extension for images         , readerTrace           :: Bool -- ^ Print debugging info         , readerTrackChanges    :: TrackChanges -} deriving (Show, Read, Data, Typeable) +} deriving (Show, Read, Data, Typeable, Generic)  instance Default ReaderOptions    where def = ReaderOptions{ @@ -279,7 +281,7 @@ instance Default ReaderOptions  -- Writer options  -- -data EPUBVersion = EPUB2 | EPUB3 deriving (Eq, Show, Read, Data, Typeable) +data EPUBVersion = EPUB2 | EPUB3 deriving (Eq, Show, Read, Data, Typeable, Generic)  data HTMLMathMethod = PlainMath                      | LaTeXMathML (Maybe String)  -- url of LaTeXMathML.js @@ -289,18 +291,18 @@ data HTMLMathMethod = PlainMath                      | MathML (Maybe String)       -- url of MathMLinHTML.js                      | MathJax String              -- url of MathJax.js                      | KaTeX String String -- url of stylesheet and katex.js -                    deriving (Show, Read, Eq, Data, Typeable) +                    deriving (Show, Read, Eq, Data, Typeable, Generic)  data CiteMethod = Citeproc                        -- use citeproc to render them                    | Natbib                        -- output natbib cite commands                    | Biblatex                      -- output biblatex cite commands -                deriving (Show, Read, Eq, Data, Typeable) +                deriving (Show, Read, Eq, Data, Typeable, Generic)  -- | Methods for obfuscating email addresses in HTML.  data ObfuscationMethod = NoObfuscation                         | ReferenceObfuscation                         | JavascriptObfuscation -                       deriving (Show, Read, Eq, Data, Typeable) +                       deriving (Show, Read, Eq, Data, Typeable, Generic)  -- | Varieties of HTML slide shows.  data HTMLSlideVariant = S5Slides @@ -309,13 +311,13 @@ data HTMLSlideVariant = S5Slides                        | DZSlides                        | RevealJsSlides                        | NoSlides -                      deriving (Show, Read, Eq, Data, Typeable) +                      deriving (Show, Read, Eq, Data, Typeable, Generic)  -- | Options for accepting or rejecting MS Word track-changes.  data TrackChanges = AcceptChanges                    | RejectChanges                    | AllChanges -                  deriving (Show, Read, Eq, Data, Typeable) +                  deriving (Show, Read, Eq, Data, Typeable, Generic)  -- | Options for writers  data WriterOptions = WriterOptions @@ -362,7 +364,7 @@ data WriterOptions = WriterOptions    , writerMediaBag         :: MediaBag       -- ^ Media collected by docx or epub reader    , writerVerbose          :: Bool           -- ^ Verbose debugging output    , writerLaTeXArgs        :: [String]       -- ^ Flags to pass to latex-engine -  } deriving (Show, Data, Typeable) +  } deriving (Show, Data, Typeable, Generic)  instance Default WriterOptions where    def = WriterOptions { writerStandalone       = False diff --git a/src/Text/Pandoc/PDF.hs b/src/Text/Pandoc/PDF.hs index 4c96908c1..ab94a289a 100644 --- a/src/Text/Pandoc/PDF.hs +++ b/src/Text/Pandoc/PDF.hs @@ -30,11 +30,11 @@ Conversion of LaTeX documents to PDF.  -}  module Text.Pandoc.PDF ( makePDF ) where -import Prelude  import Data.ByteString.Lazy (ByteString)  import qualified Data.ByteString.Lazy as B  import qualified Data.ByteString.Lazy.Char8 as BC  import qualified Data.ByteString as BS +import Text.Pandoc.Compat.Monoid ((<>))  import System.Exit (ExitCode (..))  import System.FilePath  import System.IO (stderr, stdout) diff --git a/src/Text/Pandoc/Parsing.hs b/src/Text/Pandoc/Parsing.hs index 75c557ac6..02d114e0f 100644 --- a/src/Text/Pandoc/Parsing.hs +++ b/src/Text/Pandoc/Parsing.hs @@ -180,12 +180,12 @@ import Data.Char ( toLower, toUpper, ord, chr, isAscii, isAlphaNum,                     isHexDigit, isSpace )  import Data.List ( intercalate, transpose, isSuffixOf )  import Text.Pandoc.Shared -import Prelude  import qualified Data.Map as M  import Text.TeXMath.Readers.TeX.Macros (applyMacros, Macro,                                          parseMacroDefinitions)  import Text.Pandoc.Compat.TagSoupEntity ( lookupEntity )  import Text.Pandoc.Asciify (toAsciiChar) +import Text.Pandoc.Compat.Monoid ((<>))  import Data.Default  import qualified Data.Set as Set  import Control.Monad.Reader @@ -1211,7 +1211,8 @@ citeKey = try $ do    firstChar <- alphaNum <|> char '_' <|> char '*' -- @* for wildcard in nocite    let regchar = satisfy (\c -> isAlphaNum c || c == '_')    let internal p = try $ p <* lookAhead regchar -  rest <- many $ regchar <|> internal (oneOf ":.#$%&-+?<>~/") +  rest <- many $ regchar <|> internal (oneOf ":.#$%&-+?<>~/") <|> +                 (oneOf ":/" <* lookAhead (char '/'))    let key = firstChar:rest    return (suppress_author, key) diff --git a/src/Text/Pandoc/Pretty.hs b/src/Text/Pandoc/Pretty.hs index 2589f7f6b..5771f3a89 100644 --- a/src/Text/Pandoc/Pretty.hs +++ b/src/Text/Pandoc/Pretty.hs @@ -74,13 +74,13 @@ module Text.Pandoc.Pretty (       )  where -import Prelude  import Data.Sequence (Seq, fromList, (<|), singleton, mapWithIndex, viewl, ViewL(..))  import Data.Foldable (toList)  import Data.List (intercalate)  import Data.String  import Control.Monad.State  import Data.Char (isSpace) +import Text.Pandoc.Compat.Monoid ((<>))  data RenderState a = RenderState{           output       :: [a]        -- ^ In reverse order diff --git a/src/Text/Pandoc/Process.hs b/src/Text/Pandoc/Process.hs index 77b009d96..e5245638d 100644 --- a/src/Text/Pandoc/Process.hs +++ b/src/Text/Pandoc/Process.hs @@ -29,7 +29,6 @@ ByteString variant of 'readProcessWithExitCode'.  -}  module Text.Pandoc.Process (pipeProcess)  where -import Prelude  import System.Process  import System.Exit (ExitCode (..))  import Control.Exception diff --git a/src/Text/Pandoc/Readers/CommonMark.hs b/src/Text/Pandoc/Readers/CommonMark.hs index e6f8026ab..51a35c8ad 100644 --- a/src/Text/Pandoc/Readers/CommonMark.hs +++ b/src/Text/Pandoc/Readers/CommonMark.hs @@ -32,7 +32,6 @@ CommonMark is a strongly specified variant of Markdown: http://commonmark.org.  module Text.Pandoc.Readers.CommonMark (readCommonMark)  where -import Prelude  import CMark  import Data.Text (unpack, pack)  import Data.List (groupBy) diff --git a/src/Text/Pandoc/Readers/DocBook.hs b/src/Text/Pandoc/Readers/DocBook.hs index 0845f5e03..f679ddb57 100644 --- a/src/Text/Pandoc/Readers/DocBook.hs +++ b/src/Text/Pandoc/Readers/DocBook.hs @@ -1,5 +1,4 @@  module Text.Pandoc.Readers.DocBook ( readDocBook ) where -import Prelude  import Data.Char (toUpper)  import Text.Pandoc.Shared (safeRead)  import Text.Pandoc.Options diff --git a/src/Text/Pandoc/Readers/Docx.hs b/src/Text/Pandoc/Readers/Docx.hs index 35b2ba3fd..9f1c7af0a 100644 --- a/src/Text/Pandoc/Readers/Docx.hs +++ b/src/Text/Pandoc/Readers/Docx.hs @@ -74,7 +74,6 @@ module Text.Pandoc.Readers.Docx         ( readDocx         ) where -import Prelude  import Codec.Archive.Zip  import Text.Pandoc.Definition  import Text.Pandoc.Options @@ -504,6 +503,10 @@ bodyPartToBlocks (ListItem pPr numId lvl levelInfo parparts) = do                                     ]    blks <- bodyPartToBlocks (Paragraph pPr parparts)    return $ divWith ("", ["list-item"], kvs) blks +bodyPartToBlocks (DummyListItem pPr _ parparts) =  +  let pPr' = pPr {pStyle = "ListParagraph": (pStyle pPr)} +  in +    bodyPartToBlocks $ Paragraph pPr' parparts  bodyPartToBlocks (Tbl _ _ _ []) =    return $ para mempty  bodyPartToBlocks (Tbl cap _ look (r:rs)) = do diff --git a/src/Text/Pandoc/Readers/Docx/Fonts.hs b/src/Text/Pandoc/Readers/Docx/Fonts.hs index 967ca296c..b44c71412 100644 --- a/src/Text/Pandoc/Readers/Docx/Fonts.hs +++ b/src/Text/Pandoc/Readers/Docx/Fonts.hs @@ -29,7 +29,6 @@ Utilities to convert between font codepoints and unicode characters.  -}  module Text.Pandoc.Readers.Docx.Fonts (getUnicode, Font(..)) where -import Prelude  -- | Enumeration of recognised fonts  data Font = Symbol -- ^ <http://en.wikipedia.org/wiki/Symbol_(typeface) Adobe Symbol> diff --git a/src/Text/Pandoc/Readers/Docx/Lists.hs b/src/Text/Pandoc/Readers/Docx/Lists.hs index 0c9297139..c265ad074 100644 --- a/src/Text/Pandoc/Readers/Docx/Lists.hs +++ b/src/Text/Pandoc/Readers/Docx/Lists.hs @@ -33,7 +33,6 @@ module Text.Pandoc.Readers.Docx.Lists ( blocksToBullets                                        , listParagraphDivs                                        ) where -import Prelude  import Text.Pandoc.JSON  import Text.Pandoc.Generic (bottomUp)  import Text.Pandoc.Shared (trim) diff --git a/src/Text/Pandoc/Readers/Docx/Parse.hs b/src/Text/Pandoc/Readers/Docx/Parse.hs index 91eab1339..5910a476b 100644 --- a/src/Text/Pandoc/Readers/Docx/Parse.hs +++ b/src/Text/Pandoc/Readers/Docx/Parse.hs @@ -50,7 +50,6 @@ module Text.Pandoc.Readers.Docx.Parse ( Docx(..)                                        , Cell(..)                                        , archiveToDocx                                        ) where -import Prelude  import Codec.Archive.Zip  import Text.XML.Light  import Data.Maybe @@ -76,6 +75,7 @@ data ReaderEnv = ReaderEnv { envNotes         :: Notes                             , envFont          :: Maybe Font                             , envCharStyles    :: CharStyleMap                             , envParStyles     :: ParStyleMap +                           , envLocation      :: DocumentLocation                             }                 deriving Show @@ -88,7 +88,7 @@ instance Error DocxError where  type D = ExceptT DocxError (Reader ReaderEnv)  runD :: D a -> ReaderEnv -> Either DocxError a -runD dx re = runReader (runExceptT dx ) re +runD dx re = runReader (runExceptT dx) re  maybeToD :: Maybe a -> D a  maybeToD (Just a) = return a @@ -141,7 +141,10 @@ data AbstractNumb = AbstractNumb String [Level]  -- (ilvl, format, string, start)  type Level = (String, String, String, Maybe Integer) -data Relationship = Relationship (RelId, Target) +data DocumentLocation = InDocument | InFootnote | InEndnote +                      deriving (Eq,Show) + +data Relationship = Relationship DocumentLocation RelId Target                    deriving Show  data Notes = Notes NameSpaces @@ -175,6 +178,7 @@ defaultParagraphStyle = ParagraphStyle { pStyle = []  data BodyPart = Paragraph ParagraphStyle [ParPart]                | ListItem ParagraphStyle String String Level [ParPart] +              | DummyListItem ParagraphStyle String [ParPart]                | Tbl String TblGrid TblLook [Row]                | OMathPara [Exp]                deriving Show @@ -239,7 +243,6 @@ defaultRunStyle = RunStyle { isBold = Nothing                             , rUnderline = Nothing                             , rStyle = Nothing} -  type Target = String  type Anchor = String  type URL = String @@ -256,7 +259,8 @@ archiveToDocx archive = do        rels      = archiveToRelationships archive        media     = archiveToMedia archive        (styles, parstyles) = archiveToStyles archive -      rEnv = ReaderEnv notes numbering rels media Nothing styles parstyles +      rEnv = +        ReaderEnv notes numbering rels media Nothing styles parstyles InDocument    doc <- runD (archiveToDocument archive) rEnv    return $ Docx doc @@ -363,29 +367,30 @@ archiveToNotes zf =    in     Notes ns fn en -filePathIsRel :: FilePath -> Bool -filePathIsRel fp = -  let (dir, name) = splitFileName fp -  in -   (dir == "word/_rels/") && ((takeExtension name) == ".rels") +filePathToRelType :: FilePath -> Maybe DocumentLocation +filePathToRelType "word/_rels/document.xml.rels" = Just InDocument +filePathToRelType "word/_rels/footnotes.xml.rels" = Just InFootnote +filePathToRelType "word/_rels/endnotes.xml.rels" = Just InEndnote +filePathToRelType _ = Nothing -relElemToRelationship :: Element -> Maybe Relationship -relElemToRelationship element | qName (elName element) == "Relationship" = +relElemToRelationship :: DocumentLocation -> Element -> Maybe Relationship +relElemToRelationship relType element | qName (elName element) == "Relationship" =    do      relId <- findAttr (QName "Id" Nothing Nothing) element      target <- findAttr (QName "Target" Nothing Nothing) element -    return $ Relationship (relId, target) -relElemToRelationship _ = Nothing - - +    return $ Relationship relType relId target +relElemToRelationship _ _ = Nothing + +filePathToRelationships :: Archive -> FilePath -> [Relationship] +filePathToRelationships ar fp | Just relType <- filePathToRelType fp +                              , Just entry <- findEntryByPath fp ar +                              , Just relElems <- (parseXMLDoc . UTF8.toStringLazy . fromEntry) entry = +  mapMaybe (relElemToRelationship relType) $ elChildren relElems +filePathToRelationships _ _ = [] +                                 archiveToRelationships :: Archive -> [Relationship]  archiveToRelationships archive = -  let relPaths = filter filePathIsRel (filesInArchive archive) -      entries  = mapMaybe (\f -> findEntryByPath f archive) relPaths -      relElems = mapMaybe (parseXMLDoc . UTF8.toStringLazy . fromEntry) entries -      rels =     mapMaybe relElemToRelationship $ concatMap elChildren relElems -  in -   rels +  concatMap (filePathToRelationships archive) $ filesInArchive archive  filePathIsMedia :: FilePath -> Bool  filePathIsMedia fp = @@ -410,6 +415,7 @@ lookupLevel numId ilvl (Numbering _ numbs absNumbs) = do    lvl  <- lookup ilvl $ map (\l@(i, _, _, _) -> (i, l)) lvls    return lvl +  numElemToNum :: NameSpaces -> Element -> Maybe Numb  numElemToNum ns element |    qName (elName element) == "num" && @@ -561,7 +567,7 @@ elemToBodyPart ns element      num <- asks envNumbering      case lookupLevel numId lvl num of       Just levelInfo -> return $ ListItem parstyle numId lvl levelInfo parparts -     Nothing        -> throwError WrongElem +     Nothing        -> return $ DummyListItem parstyle lvl parparts  elemToBodyPart ns element    | isElem ns "w" "p" element = do        sty <- asks envParStyles @@ -574,7 +580,7 @@ elemToBodyPart ns element            Just levelInfo ->              return $ ListItem parstyle numId lvl levelInfo parparts            Nothing         -> -            throwError WrongElem +            return $ DummyListItem parstyle lvl parparts         Nothing -> return $ Paragraph parstyle parparts  elemToBodyPart ns element    | isElem ns "w" "tbl" element = do @@ -597,13 +603,16 @@ elemToBodyPart ns element      return $ Tbl caption grid tblLook rows  elemToBodyPart _ _ = throwError WrongElem -lookupRelationship :: RelId -> [Relationship] -> Maybe Target -lookupRelationship relid rels = -  lookup relid (map (\(Relationship pair) -> pair) rels) +lookupRelationship :: DocumentLocation -> RelId -> [Relationship] -> Maybe Target +lookupRelationship docLocation relid rels = +  lookup (docLocation, relid) pairs +  where +    pairs = map (\(Relationship loc relid' target) -> ((loc, relid'), target)) rels  expandDrawingId :: String -> D (FilePath, B.ByteString)  expandDrawingId s = do -  target <- asks (lookupRelationship s . envRelationships) +  location <- asks envLocation +  target <- asks (lookupRelationship location s . envRelationships)    case target of      Just filepath -> do        bytes <- asks (lookup ("word/" ++ filepath) . envMedia) @@ -658,9 +667,10 @@ elemToParPart ns element  elemToParPart ns element    | isElem ns "w" "hyperlink" element    , Just relId <- findAttr (elemName ns "r" "id") element = do +    location <- asks envLocation      runs <- mapD (elemToRun ns) (elChildren element)      rels <- asks envRelationships -    case lookupRelationship relId rels of +    case lookupRelationship location relId rels of        Just target -> do           case findAttr (elemName ns "w" "anchor") element of               Just anchor -> return $ ExternalHyperLink (target ++ '#':anchor) runs @@ -700,7 +710,7 @@ elemToRun ns element    , Just fnId <- findAttr (elemName ns "w" "id") ref = do      notes <- asks envNotes      case lookupFootnote fnId notes of -      Just e -> do bps <- mapD (elemToBodyPart ns) (elChildren e) +      Just e -> do bps <- local (\r -> r {envLocation=InFootnote}) $ mapD (elemToBodyPart ns) (elChildren e)                     return $ Footnote bps        Nothing  -> return $ Footnote []  elemToRun ns element @@ -709,7 +719,7 @@ elemToRun ns element    , Just enId <- findAttr (elemName ns "w" "id") ref = do      notes <- asks envNotes      case lookupEndnote enId notes of -      Just e -> do bps <- mapD (elemToBodyPart ns) (elChildren e) +      Just e -> do bps <- local (\r -> r {envLocation=InEndnote}) $ mapD (elemToBodyPart ns) (elChildren e)                     return $ Endnote bps        Nothing  -> return $ Endnote []  elemToRun ns element diff --git a/src/Text/Pandoc/Readers/Docx/Reducible.hs b/src/Text/Pandoc/Readers/Docx/Reducible.hs index a850141f6..c93b40119 100644 --- a/src/Text/Pandoc/Readers/Docx/Reducible.hs +++ b/src/Text/Pandoc/Readers/Docx/Reducible.hs @@ -7,7 +7,6 @@ module Text.Pandoc.Readers.Docx.Reducible ( concatReduce         where -import Prelude  import Text.Pandoc.Builder  import Data.List  import Data.Sequence (ViewR(..), ViewL(..), viewl, viewr) diff --git a/src/Text/Pandoc/Readers/Docx/StyleMap.hs b/src/Text/Pandoc/Readers/Docx/StyleMap.hs index 231653106..2901ea2a3 100644 --- a/src/Text/Pandoc/Readers/Docx/StyleMap.hs +++ b/src/Text/Pandoc/Readers/Docx/StyleMap.hs @@ -5,7 +5,6 @@ module Text.Pandoc.Readers.Docx.StyleMap (  StyleMaps(..)                                            , hasStyleName                                            ) where -import Prelude  import           Text.XML.Light  import           Text.Pandoc.Readers.Docx.Util  import           Control.Monad.State diff --git a/src/Text/Pandoc/Readers/Docx/Util.hs b/src/Text/Pandoc/Readers/Docx/Util.hs index 2790c0d1a..891f107b0 100644 --- a/src/Text/Pandoc/Readers/Docx/Util.hs +++ b/src/Text/Pandoc/Readers/Docx/Util.hs @@ -5,7 +5,6 @@ module Text.Pandoc.Readers.Docx.Util (                                        , elemToNameSpaces                                        ) where -import Prelude  import Text.XML.Light  import Data.Maybe (mapMaybe) diff --git a/src/Text/Pandoc/Readers/EPUB.hs b/src/Text/Pandoc/Readers/EPUB.hs index 9938bb70b..b8698fe26 100644 --- a/src/Text/Pandoc/Readers/EPUB.hs +++ b/src/Text/Pandoc/Readers/EPUB.hs @@ -8,7 +8,6 @@ module Text.Pandoc.Readers.EPUB    (readEPUB)    where -import Prelude  import Text.XML.Light  import Text.Pandoc.Definition hiding (Attr)  import Text.Pandoc.Walk (walk, query) @@ -17,6 +16,7 @@ import Text.Pandoc.Options ( ReaderOptions(..), readerTrace)  import Text.Pandoc.Shared (escapeURI, collapseFilePath, addMetaField)  import Text.Pandoc.MediaBag (MediaBag, insertMedia)  import Text.Pandoc.Compat.Except (MonadError, throwError, runExcept, Except) +import Text.Pandoc.Compat.Monoid ((<>))  import Text.Pandoc.MIME (MimeType)  import qualified Text.Pandoc.Builder as B  import Codec.Archive.Zip ( Archive (..), toArchive, fromEntry diff --git a/src/Text/Pandoc/Readers/HTML.hs b/src/Text/Pandoc/Readers/HTML.hs index 570efc2be..ce10a289e 100644 --- a/src/Text/Pandoc/Readers/HTML.hs +++ b/src/Text/Pandoc/Readers/HTML.hs @@ -38,7 +38,6 @@ module Text.Pandoc.Readers.HTML ( readHtml                                  , isCommentTag                                  ) where -import Prelude  import Text.HTML.TagSoup  import Text.HTML.TagSoup.Match  import Text.Pandoc.Definition @@ -67,7 +66,7 @@ import Control.Monad.Reader (Reader,ask, asks, local, runReader)  import Network.URI (isURI)  import Text.Pandoc.Error  import Text.Pandoc.CSS (foldOrElse, pickStyleAttrProps) - +import Text.Pandoc.Compat.Monoid ((<>))  import Text.Parsec.Error diff --git a/src/Text/Pandoc/Readers/Haddock.hs b/src/Text/Pandoc/Readers/Haddock.hs index 578a89d21..16f3d7ef3 100644 --- a/src/Text/Pandoc/Readers/Haddock.hs +++ b/src/Text/Pandoc/Readers/Haddock.hs @@ -14,9 +14,9 @@ module Text.Pandoc.Readers.Haddock      ( readHaddock      ) where -import Prelude  import Text.Pandoc.Builder (Blocks, Inlines)  import qualified Text.Pandoc.Builder as B +import Text.Pandoc.Compat.Monoid ((<>))  import Text.Pandoc.Shared (trim, splitBy)  import Data.List (intersperse, stripPrefix)  import Data.Maybe (fromMaybe) @@ -130,7 +130,7 @@ makeExample prompt expression result =          <> (mconcat $ intersperse B.linebreak $ map coder result')    where      -- 1. drop trailing whitespace from the prompt, remember the prefix -    prefix = takeWhile (`elem` [' ','\t']) prompt +    prefix = takeWhile (`elem` " \t") prompt      -- 2. drop, if possible, the exact same sequence of whitespace      -- characters from each result line diff --git a/src/Text/Pandoc/Readers/LaTeX.hs b/src/Text/Pandoc/Readers/LaTeX.hs index ffb4182ad..b9645d034 100644 --- a/src/Text/Pandoc/Readers/LaTeX.hs +++ b/src/Text/Pandoc/Readers/LaTeX.hs @@ -35,7 +35,6 @@ module Text.Pandoc.Readers.LaTeX ( readLaTeX,                                     handleIncludes                                   ) where -import Prelude  import Text.Pandoc.Definition  import Text.Pandoc.Walk  import Text.Pandoc.Shared @@ -170,17 +169,23 @@ quoted' f starter ender = do    try ((f . mconcat) <$> manyTill inline ender) <|> lit startchs  doubleQuote :: LP Inlines -doubleQuote = -      quoted' doubleQuoted (try $ string "``") (void $ try $ string "''") -  <|> quoted' doubleQuoted (string "“")        (void $ char '”') -  -- the following is used by babel for localized quotes: -  <|> quoted' doubleQuoted (try $ string "\"`") (void $ try $ string "\"'") -  <|> quoted' doubleQuoted (string "\"")       (void $ char '"') +doubleQuote = do +  smart <- getOption readerSmart +  if smart +     then quoted' doubleQuoted (try $ string "``") (void $ try $ string "''") +        <|> quoted' doubleQuoted (string "“")        (void $ char '”') +        -- the following is used by babel for localized quotes: +        <|> quoted' doubleQuoted (try $ string "\"`") (void $ try $ string "\"'") +        <|> quoted' doubleQuoted (string "\"")       (void $ char '"') +     else str <$> many1 (oneOf "`'“”\"")  singleQuote :: LP Inlines -singleQuote = -      quoted' singleQuoted (string "`") (try $ char '\'' >> notFollowedBy letter) -  <|> quoted' singleQuoted (string "‘") (try $ char '’' >> notFollowedBy letter) +singleQuote = do +  smart <- getOption readerSmart +  if smart +     then quoted' singleQuoted (string "`") (try $ char '\'' >> notFollowedBy letter) +      <|> quoted' singleQuoted (string "‘") (try $ char '’' >> notFollowedBy letter) +     else str <$> many1 (oneOf "`\'‘’")  inline :: LP Inlines  inline = (mempty <$ comment) diff --git a/src/Text/Pandoc/Readers/Markdown.hs b/src/Text/Pandoc/Readers/Markdown.hs index d3b71c499..7e811a966 100644 --- a/src/Text/Pandoc/Readers/Markdown.hs +++ b/src/Text/Pandoc/Readers/Markdown.hs @@ -32,7 +32,6 @@ Conversion of markdown-formatted plain text to 'Pandoc' document.  module Text.Pandoc.Readers.Markdown ( readMarkdown,                                        readMarkdownWithWarnings ) where -import Prelude  import Data.List ( transpose, sortBy, findIndex, intersperse, intercalate )  import qualified Data.Map as M  import Data.Scientific (coefficient, base10Exponent) @@ -40,6 +39,7 @@ import Data.Ord ( comparing )  import Data.Char ( isSpace, isAlphaNum, toLower )  import Data.Maybe  import Text.Pandoc.Definition +import Text.Pandoc.Emoji (emojis)  import qualified Data.Text as T  import Data.Text (Text)  import qualified Data.Yaml as Yaml @@ -63,6 +63,7 @@ import Text.HTML.TagSoup.Match (tagOpen)  import qualified Data.Set as Set  import Text.Printf (printf)  import Debug.Trace (trace) +import Text.Pandoc.Compat.Monoid ((<>))  import Text.Pandoc.Error  type MarkdownParser = Parser [Char] ParserState @@ -1467,6 +1468,7 @@ inline = choice [ whitespace                  , exampleRef                  , smart                  , return . B.singleton <$> charRef +                , emoji                  , symbol                  , ltSign                  ] <?> "inline" @@ -1898,6 +1900,21 @@ rawHtmlInline = do                               else not . isTextTag    return $ return $ B.rawInline "html" result +-- Emoji + +emojiChars :: [Char] +emojiChars = ['a'..'z'] ++ ['0'..'9'] ++ ['_','+','-'] + +emoji :: MarkdownParser (F Inlines) +emoji = try $ do +  guardEnabled Ext_emoji +  char ':' +  emojikey <- many1 (oneOf emojiChars) +  char ':' +  case M.lookup emojikey emojis of +       Just s  -> return (return (B.str s)) +       Nothing -> mzero +  -- Citations  cite :: MarkdownParser (F Inlines) diff --git a/src/Text/Pandoc/Readers/MediaWiki.hs b/src/Text/Pandoc/Readers/MediaWiki.hs index b21fb58c0..ffac51e7b 100644 --- a/src/Text/Pandoc/Readers/MediaWiki.hs +++ b/src/Text/Pandoc/Readers/MediaWiki.hs @@ -36,10 +36,10 @@ _ parse templates?  -}  module Text.Pandoc.Readers.MediaWiki ( readMediaWiki ) where -import Prelude  import Text.Pandoc.Definition  import qualified Text.Pandoc.Builder as B  import Text.Pandoc.Builder (Inlines, Blocks, trimInlines) +import Text.Pandoc.Compat.Monoid ((<>))  import Text.Pandoc.Options  import Text.Pandoc.Readers.HTML ( htmlTag, isBlockTag, isCommentTag )  import Text.Pandoc.XML ( fromEntities ) diff --git a/src/Text/Pandoc/Readers/Native.hs b/src/Text/Pandoc/Readers/Native.hs index 73ac0d4b2..4ec164e19 100644 --- a/src/Text/Pandoc/Readers/Native.hs +++ b/src/Text/Pandoc/Readers/Native.hs @@ -30,7 +30,6 @@ Conversion of a string representation of a pandoc type (@Pandoc@,  -}  module Text.Pandoc.Readers.Native ( readNative ) where -import Prelude  import Text.Pandoc.Definition  import Text.Pandoc.Shared (safeRead) diff --git a/src/Text/Pandoc/Readers/OPML.hs b/src/Text/Pandoc/Readers/OPML.hs index e7633e414..b2e5f2e67 100644 --- a/src/Text/Pandoc/Readers/OPML.hs +++ b/src/Text/Pandoc/Readers/OPML.hs @@ -1,6 +1,5 @@  {-# LANGUAGE FlexibleContexts #-}  module Text.Pandoc.Readers.OPML ( readOPML ) where -import Prelude  import Data.Char (toUpper)  import Text.Pandoc.Options  import Text.Pandoc.Definition diff --git a/src/Text/Pandoc/Readers/Odt.hs b/src/Text/Pandoc/Readers/Odt.hs index cc15c9e20..a925c1d84 100644 --- a/src/Text/Pandoc/Readers/Odt.hs +++ b/src/Text/Pandoc/Readers/Odt.hs @@ -32,7 +32,6 @@ Entry point to the odt reader.  module Text.Pandoc.Readers.Odt ( readOdt ) where -import Prelude  import           Codec.Archive.Zip  import qualified Text.XML.Light                        as XML diff --git a/src/Text/Pandoc/Readers/Odt/Arrows/State.hs b/src/Text/Pandoc/Readers/Odt/Arrows/State.hs index 2cc83183f..30f96c557 100644 --- a/src/Text/Pandoc/Readers/Odt/Arrows/State.hs +++ b/src/Text/Pandoc/Readers/Odt/Arrows/State.hs @@ -46,6 +46,7 @@ import           Control.Monad  import           Data.Foldable +import           Text.Pandoc.Compat.Monoid  import           Text.Pandoc.Readers.Odt.Arrows.Utils  import           Text.Pandoc.Readers.Odt.Generic.Fallible diff --git a/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs b/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs index e7d2bcb92..8c9ee0539 100644 --- a/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs +++ b/src/Text/Pandoc/Readers/Odt/Arrows/Utils.hs @@ -39,7 +39,6 @@ with an equivalent return value.  -- We export everything  module Text.Pandoc.Readers.Odt.Arrows.Utils where -import Prelude  import           Control.Arrow  import           Control.Monad                         ( join, MonadPlus(..) ) @@ -47,7 +46,7 @@ import qualified Data.Foldable                    as F  import           Text.Pandoc.Readers.Odt.Generic.Fallible  import           Text.Pandoc.Readers.Odt.Generic.Utils - +import           Text.Pandoc.Compat.Monoid  and2 :: (Arrow a) => a b c -> a b c' -> a b (c,c')  and2 = (&&&) diff --git a/src/Text/Pandoc/Readers/Odt/ContentReader.hs b/src/Text/Pandoc/Readers/Odt/ContentReader.hs index 06dd83668..1f1c57646 100644 --- a/src/Text/Pandoc/Readers/Odt/ContentReader.hs +++ b/src/Text/Pandoc/Readers/Odt/ContentReader.hs @@ -39,7 +39,6 @@ module Text.Pandoc.Readers.Odt.ContentReader  , read_body  ) where -import Prelude  import           Control.Arrow  import           Control.Applicative    hiding ( liftA, liftA2, liftA3 ) diff --git a/src/Text/Pandoc/Readers/Odt/Generic/Fallible.hs b/src/Text/Pandoc/Readers/Odt/Generic/Fallible.hs index 7213bc8f1..d0fdc228f 100644 --- a/src/Text/Pandoc/Readers/Odt/Generic/Fallible.hs +++ b/src/Text/Pandoc/Readers/Odt/Generic/Fallible.hs @@ -39,10 +39,9 @@ compatible instances of "ArrowChoice".  -- We export everything  module Text.Pandoc.Readers.Odt.Generic.Fallible where -import Prelude  import           Control.Applicative  import           Control.Monad - +import           Text.Pandoc.Compat.Monoid ((<>))  import qualified Data.Foldable       as F  -- | Default for now. Will probably become a class at some point. diff --git a/src/Text/Pandoc/Readers/Odt/Generic/Namespaces.hs b/src/Text/Pandoc/Readers/Odt/Generic/Namespaces.hs index 0a6095e98..82ae3e20e 100644 --- a/src/Text/Pandoc/Readers/Odt/Generic/Namespaces.hs +++ b/src/Text/Pandoc/Readers/Odt/Generic/Namespaces.hs @@ -31,7 +31,6 @@ typesafe Haskell namespace identifiers and unsafe "real world" namespaces.  module Text.Pandoc.Readers.Odt.Generic.Namespaces where -import Prelude  import qualified Data.Map as M  -- diff --git a/src/Text/Pandoc/Readers/Odt/Generic/SetMap.hs b/src/Text/Pandoc/Readers/Odt/Generic/SetMap.hs index b7a555219..afd7d616c 100644 --- a/src/Text/Pandoc/Readers/Odt/Generic/SetMap.hs +++ b/src/Text/Pandoc/Readers/Odt/Generic/SetMap.hs @@ -30,7 +30,6 @@ A map of values to sets of values.  module Text.Pandoc.Readers.Odt.Generic.SetMap where -import Prelude  import qualified Data.Map as M  import qualified Data.Set as S diff --git a/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs b/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs index a09b4cc1d..6c10ed61d 100644 --- a/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs +++ b/src/Text/Pandoc/Readers/Odt/Generic/Utils.hs @@ -53,7 +53,6 @@ module Text.Pandoc.Readers.Odt.Generic.Utils  , composition  ) where -import Prelude  import           Control.Category        ( Category, (>>>), (<<<) )  import qualified Control.Category as Cat ( id )  import           Control.Monad           ( msum ) diff --git a/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs b/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs index 7d72ee125..8c03d1a09 100644 --- a/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs +++ b/src/Text/Pandoc/Readers/Odt/Generic/XMLConverter.hs @@ -116,7 +116,6 @@ module Text.Pandoc.Readers.Odt.Generic.XMLConverter  , matchContent  ) where -import Prelude  import           Control.Applicative  hiding ( liftA, liftA2 )  import           Control.Monad               ( MonadPlus )  import           Control.Arrow diff --git a/src/Text/Pandoc/Readers/Odt/Namespaces.hs b/src/Text/Pandoc/Readers/Odt/Namespaces.hs index f00093368..deb009998 100644 --- a/src/Text/Pandoc/Readers/Odt/Namespaces.hs +++ b/src/Text/Pandoc/Readers/Odt/Namespaces.hs @@ -31,7 +31,6 @@ Namespaces used in odt files.  module Text.Pandoc.Readers.Odt.Namespaces ( Namespace (..)                                            ) where -import Prelude  import           Data.List       ( isPrefixOf )  import           Data.Maybe      ( fromMaybe, listToMaybe )  import qualified Data.Map   as M ( empty, insert ) diff --git a/src/Text/Pandoc/Readers/Odt/StyleReader.hs b/src/Text/Pandoc/Readers/Odt/StyleReader.hs index 4140bf2c7..96cfed0b3 100644 --- a/src/Text/Pandoc/Readers/Odt/StyleReader.hs +++ b/src/Text/Pandoc/Readers/Odt/StyleReader.hs @@ -70,7 +70,6 @@ module Text.Pandoc.Readers.Odt.StyleReader  , readStylesAt  ) where -import Prelude  import           Control.Arrow  import           Control.Applicative hiding ( liftA, liftA2, liftA3 ) diff --git a/src/Text/Pandoc/Readers/Org.hs b/src/Text/Pandoc/Readers/Org.hs index 6e14febeb..3be47cfd4 100644 --- a/src/Text/Pandoc/Readers/Org.hs +++ b/src/Text/Pandoc/Readers/Org.hs @@ -21,7 +21,7 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA  {- |     Module      : Text.Pandoc.Readers.Org -   Copyright   : Copyright (C) 2014 Albert Krewinkel +   Copyright   : Copyright (C) 2014-2015 Albert Krewinkel     License     : GNU GPL, version 2 or above     Maintainer  : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de> @@ -30,11 +30,11 @@ Conversion of org-mode formatted plain text to 'Pandoc' document.  -}  module Text.Pandoc.Readers.Org ( readOrg ) where -import Prelude  import qualified Text.Pandoc.Builder as B  import           Text.Pandoc.Builder ( Inlines, Blocks, HasMeta(..),                                         trimInlines )  import           Text.Pandoc.Definition +import           Text.Pandoc.Compat.Monoid ((<>))  import           Text.Pandoc.Options  import qualified Text.Pandoc.Parsing as P  import           Text.Pandoc.Parsing hiding ( F, unF, askF, asksF, runF @@ -994,13 +994,16 @@ definitionListItem :: OrgParser Int                     -> OrgParser (F (Inlines, [Blocks]))  definitionListItem parseMarkerGetLength = try $ do    markerLength <- parseMarkerGetLength -  term <- manyTill (noneOf "\n\r") (try $ string "::") +  term <- manyTill (noneOf "\n\r") (try definitionMarker)    line1 <- anyLineNewline    blank <- option "" ("\n" <$ blankline)    cont <- concat <$> many (listContinuation markerLength)    term' <- parseFromString parseInlines term    contents' <- parseFromString parseBlocks $ line1 ++ blank ++ cont    return $ (,) <$> term' <*> fmap (:[]) contents' + where +   definitionMarker = +     spaceChar *> string "::" <* (spaceChar <|> lookAhead P.newline)  -- parse raw text for one list item, excluding start marker and continuations @@ -1585,8 +1588,11 @@ smart :: OrgParser (F Inlines)  smart = do    getOption readerSmart >>= guard    doubleQuoted <|> singleQuoted <|> -    choice (map (return <$>) [orgApostrophe, dash, ellipses]) -  where orgApostrophe = +    choice (map (return <$>) [orgApostrophe, orgDash, orgEllipses]) +  where +    orgDash = dash <* updatePositions '-' +    orgEllipses = ellipses <* updatePositions '.' +    orgApostrophe =            (char '\'' <|> char '\8217') <* updateLastPreCharPos                                         <* updateLastForbiddenCharPos                                         *> return (B.str "\x2019") @@ -1594,9 +1600,10 @@ smart = do  singleQuoted :: OrgParser (F Inlines)  singleQuoted = try $ do    singleQuoteStart +  updatePositions '\''    withQuoteContext InSingleQuote $      fmap B.singleQuoted . trimInlinesF . mconcat <$> -      many1Till inline singleQuoteEnd +      many1Till inline (singleQuoteEnd <* updatePositions '\'')  -- doubleQuoted will handle regular double-quoted sections, as well  -- as dialogues with an open double-quote without a close double-quote @@ -1604,6 +1611,7 @@ singleQuoted = try $ do  doubleQuoted :: OrgParser (F Inlines)  doubleQuoted = try $ do    doubleQuoteStart +  updatePositions '"'    contents <- mconcat <$> many (try $ notFollowedBy doubleQuoteEnd >> inline)    (withQuoteContext InDoubleQuote $ (doubleQuoteEnd <* updateLastForbiddenCharPos) >> return         (fmap B.doubleQuoted . trimInlinesF $ contents)) diff --git a/src/Text/Pandoc/Readers/RST.hs b/src/Text/Pandoc/Readers/RST.hs index 82fa67407..199e7f3f8 100644 --- a/src/Text/Pandoc/Readers/RST.hs +++ b/src/Text/Pandoc/Readers/RST.hs @@ -33,7 +33,6 @@ module Text.Pandoc.Readers.RST (                                  readRST,                                  readRSTWithWarnings                                 ) where -import Prelude  import Text.Pandoc.Definition  import Text.Pandoc.Builder (setMeta, fromList)  import Text.Pandoc.Shared @@ -49,7 +48,7 @@ import Text.Pandoc.Builder (Inlines, Blocks, trimInlines)  import qualified Text.Pandoc.Builder as B  import Data.Sequence (viewr, ViewR(..))  import Data.Char (toLower, isHexDigit, isSpace) - +import Text.Pandoc.Compat.Monoid ((<>))  import Text.Pandoc.Error  -- | Parse reStructuredText string and return Pandoc document. diff --git a/src/Text/Pandoc/Readers/TWiki.hs b/src/Text/Pandoc/Readers/TWiki.hs index 558e9691a..fc2bdc069 100644 --- a/src/Text/Pandoc/Readers/TWiki.hs +++ b/src/Text/Pandoc/Readers/TWiki.hs @@ -33,7 +33,6 @@ module Text.Pandoc.Readers.TWiki ( readTWiki                                   , readTWikiWithWarnings                                   ) where -import Prelude  import Text.Pandoc.Definition  import qualified Text.Pandoc.Builder as B  import Text.Pandoc.Options diff --git a/src/Text/Pandoc/Readers/TeXMath.hs b/src/Text/Pandoc/Readers/TeXMath.hs index ad0eacb2b..e5778b123 100644 --- a/src/Text/Pandoc/Readers/TeXMath.hs +++ b/src/Text/Pandoc/Readers/TeXMath.hs @@ -29,7 +29,6 @@ Conversion of TeX math to a list of 'Pandoc' inline elements.  -}  module Text.Pandoc.Readers.TeXMath ( texMathToInlines ) where -import Prelude  import Text.Pandoc.Definition  import Text.TeXMath diff --git a/src/Text/Pandoc/Readers/Textile.hs b/src/Text/Pandoc/Readers/Textile.hs index a99831a56..3db01faf4 100644 --- a/src/Text/Pandoc/Readers/Textile.hs +++ b/src/Text/Pandoc/Readers/Textile.hs @@ -51,7 +51,6 @@ TODO : refactor common patterns across readers :  module Text.Pandoc.Readers.Textile ( readTextile) where -import Prelude  import Text.Pandoc.Definition  import Text.Pandoc.Builder (Inlines, Blocks, trimInlines)  import qualified Text.Pandoc.Builder as B @@ -65,6 +64,7 @@ import Text.HTML.TagSoup.Match  import Data.List ( intercalate )  import Data.Char ( digitToInt, isUpper)  import Control.Monad ( guard, liftM, when ) +import Text.Pandoc.Compat.Monoid ((<>))  import Text.Printf  import Debug.Trace (trace)  import Text.Pandoc.Error @@ -535,6 +535,7 @@ link = try $ do  image :: Parser [Char] ParserState Inlines  image = try $ do    char '!' >> notFollowedBy space +  _ <- attributes -- ignore for now, until we have image attributes    src <- manyTill anyChar' (lookAhead $ oneOf "!(")    alt <- option "" (try $ (char '(' >> manyTill anyChar' (char ')')))    char '!' diff --git a/src/Text/Pandoc/Readers/Txt2Tags.hs b/src/Text/Pandoc/Readers/Txt2Tags.hs index 3a3172734..58841f2ce 100644 --- a/src/Text/Pandoc/Readers/Txt2Tags.hs +++ b/src/Text/Pandoc/Readers/Txt2Tags.hs @@ -32,9 +32,9 @@ module Text.Pandoc.Readers.Txt2Tags ( readTxt2Tags                                      , readTxt2TagsNoMacros)                                      where -import Prelude  import qualified Text.Pandoc.Builder as B  import Text.Pandoc.Builder ( Inlines, Blocks, trimInlines ) +import Text.Pandoc.Compat.Monoid ((<>))  import Text.Pandoc.Definition  import Text.Pandoc.Options  import Text.Pandoc.Shared (escapeURI,compactify', compactify'DL) diff --git a/src/Text/Pandoc/SelfContained.hs b/src/Text/Pandoc/SelfContained.hs index 16013f466..390a7a21a 100644 --- a/src/Text/Pandoc/SelfContained.hs +++ b/src/Text/Pandoc/SelfContained.hs @@ -31,7 +31,6 @@ offline, by incorporating linked images, CSS, and scripts into  the HTML using data URIs.  -}  module Text.Pandoc.SelfContained ( makeSelfContained ) where -import Prelude  import Text.HTML.TagSoup  import Network.URI (isURI, escapeURIString, URI(..), parseURI)  import Data.ByteString.Base64 diff --git a/src/Text/Pandoc/Shared.hs b/src/Text/Pandoc/Shared.hs index 91ccfb134..448a582aa 100644 --- a/src/Text/Pandoc/Shared.hs +++ b/src/Text/Pandoc/Shared.hs @@ -97,7 +97,6 @@ module Text.Pandoc.Shared (                       pandocVersion                      ) where -import Prelude  import Text.Pandoc.Definition  import Text.Pandoc.Walk  import Text.Pandoc.MediaBag (MediaBag, lookupMedia) @@ -130,6 +129,7 @@ import System.IO (stderr)  import System.IO.Temp  import Text.HTML.TagSoup (renderTagsOptions, RenderOptions(..), Tag(..),           renderOptions) +import Text.Pandoc.Compat.Monoid ((<>))  import qualified Data.ByteString as BS  import qualified Data.ByteString.Char8 as B8  import Data.ByteString.Base64 (decodeLenient) @@ -247,7 +247,7 @@ trim = triml . trimr  -- | Remove leading space (including newlines) from string.  triml :: String -> String -triml = dropWhile (`elem` [' ','\r','\n','\t']) +triml = dropWhile (`elem` " \r\n\t")  -- | Remove trailing space (including newlines) from string.  trimr :: String -> String @@ -660,7 +660,7 @@ inlineListToIdentifier :: [Inline] -> String  inlineListToIdentifier =    dropWhile (not . isAlpha) . intercalate "-" . words .      map (nbspToSp . toLower) . -    filter (\c -> isLetter c || isDigit c || c `elem` ['_','-','.',' ']) . +    filter (\c -> isLetter c || isDigit c || c `elem` "_-. ") .      stringify   where nbspToSp '\160'     =  ' '         nbspToSp x          =  x diff --git a/src/Text/Pandoc/Slides.hs b/src/Text/Pandoc/Slides.hs index 7fdb9d7c4..878c900f7 100644 --- a/src/Text/Pandoc/Slides.hs +++ b/src/Text/Pandoc/Slides.hs @@ -29,7 +29,6 @@ Utility functions for splitting documents into slides for slide  show formats (dzslides, revealjs, s5, slidy, slideous, beamer).  -}  module Text.Pandoc.Slides ( getSlideLevel, prepSlides ) where -import Prelude  import Text.Pandoc.Definition  -- | Find level of header that starts slides (defined as the least header diff --git a/src/Text/Pandoc/Templates.hs b/src/Text/Pandoc/Templates.hs index 027996703..a010433fa 100644 --- a/src/Text/Pandoc/Templates.hs +++ b/src/Text/Pandoc/Templates.hs @@ -93,12 +93,12 @@ module Text.Pandoc.Templates ( renderTemplate                               , Template                               , getDefaultTemplate ) where -import Prelude  import Data.Char (isAlphaNum)  import Control.Monad (guard, when)  import Data.Aeson (ToJSON(..), Value(..))  import qualified Text.Parsec as P  import Text.Parsec.Text (Parser) +import Text.Pandoc.Compat.Monoid ((<>))  import qualified Data.Text as T  import Data.Text (Text)  import Data.Text.Encoding (encodeUtf8) diff --git a/src/Text/Pandoc/UUID.hs b/src/Text/Pandoc/UUID.hs index a99be725d..463be044c 100644 --- a/src/Text/Pandoc/UUID.hs +++ b/src/Text/Pandoc/UUID.hs @@ -31,7 +31,6 @@ in RFC4122. See http://tools.ietf.org/html/rfc4122  module Text.Pandoc.UUID ( UUID, getRandomUUID ) where -import Prelude  import Text.Printf ( printf )  import System.Random ( randomIO )  import Data.Word diff --git a/src/Text/Pandoc/Writers/AsciiDoc.hs b/src/Text/Pandoc/Writers/AsciiDoc.hs index 832bd5fec..c3406f31f 100644 --- a/src/Text/Pandoc/Writers/AsciiDoc.hs +++ b/src/Text/Pandoc/Writers/AsciiDoc.hs @@ -37,7 +37,6 @@ that it has omitted the construct.  AsciiDoc:  <http://www.methods.co.nz/asciidoc/>  -}  module Text.Pandoc.Writers.AsciiDoc (writeAsciiDoc) where -import Prelude  import Text.Pandoc.Definition  import Text.Pandoc.Templates (renderTemplate')  import Text.Pandoc.Shared diff --git a/src/Text/Pandoc/Writers/CommonMark.hs b/src/Text/Pandoc/Writers/CommonMark.hs index 38cfcd82c..fee36d454 100644 --- a/src/Text/Pandoc/Writers/CommonMark.hs +++ b/src/Text/Pandoc/Writers/CommonMark.hs @@ -31,7 +31,6 @@ CommonMark:  <http://commonmark.org>  -}  module Text.Pandoc.Writers.CommonMark (writeCommonMark) where -import Prelude  import Text.Pandoc.Writers.HTML (writeHtmlString)  import Text.Pandoc.Definition  import Text.Pandoc.Shared (isTightList) diff --git a/src/Text/Pandoc/Writers/ConTeXt.hs b/src/Text/Pandoc/Writers/ConTeXt.hs index 562c9e015..61e62aa17 100644 --- a/src/Text/Pandoc/Writers/ConTeXt.hs +++ b/src/Text/Pandoc/Writers/ConTeXt.hs @@ -29,7 +29,6 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA  Conversion of 'Pandoc' format into ConTeXt.  -}  module Text.Pandoc.Writers.ConTeXt ( writeConTeXt ) where -import Prelude  import Text.Pandoc.Definition  import Text.Pandoc.Shared  import Text.Pandoc.Writers.Shared diff --git a/src/Text/Pandoc/Writers/Custom.hs b/src/Text/Pandoc/Writers/Custom.hs index ac8e8cf36..8b7dde3e5 100644 --- a/src/Text/Pandoc/Writers/Custom.hs +++ b/src/Text/Pandoc/Writers/Custom.hs @@ -35,7 +35,6 @@ Conversion of 'Pandoc' documents to custom markup using  a lua writer.  -}  module Text.Pandoc.Writers.Custom ( writeCustom ) where -import Prelude  import Text.Pandoc.Definition  import Text.Pandoc.Options  import Data.List ( intersperse ) diff --git a/src/Text/Pandoc/Writers/Docbook.hs b/src/Text/Pandoc/Writers/Docbook.hs index bedaaf690..8f9eecea8 100644 --- a/src/Text/Pandoc/Writers/Docbook.hs +++ b/src/Text/Pandoc/Writers/Docbook.hs @@ -29,7 +29,6 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA  Conversion of 'Pandoc' documents to Docbook XML.  -}  module Text.Pandoc.Writers.Docbook ( writeDocbook) where -import Prelude  import Text.Pandoc.Definition  import Text.Pandoc.XML  import Text.Pandoc.Shared diff --git a/src/Text/Pandoc/Writers/Docx.hs b/src/Text/Pandoc/Writers/Docx.hs index eabf9fb05..94c9ff28e 100644 --- a/src/Text/Pandoc/Writers/Docx.hs +++ b/src/Text/Pandoc/Writers/Docx.hs @@ -29,7 +29,6 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA  Conversion of 'Pandoc' documents to docx.  -}  module Text.Pandoc.Writers.Docx ( writeDocx ) where -import Prelude  import Data.List ( intercalate, isPrefixOf, isSuffixOf )  import qualified Data.ByteString as B  import qualified Data.ByteString.Lazy as BL @@ -61,6 +60,7 @@ import Data.Unique (hashUnique, newUnique)  import System.Random (randomRIO)  import Text.Printf (printf)  import qualified Control.Exception as E +import Text.Pandoc.Compat.Monoid ((<>))  import Text.Pandoc.MIME (MimeType, getMimeType, getMimeTypeDef,                           extensionFromMimeType)  import Control.Applicative ((<|>)) @@ -1070,8 +1070,8 @@ inlineToOpenXML opts (Note bs) = do                     [ mknode "w:rPr" [] footnoteStyle                     , mknode "w:footnoteRef" [] () ]    let notemarkerXml = RawInline (Format "openxml") $ ppElement notemarker -  let insertNoteRef (Plain ils : xs) = Plain (notemarkerXml : ils) : xs -      insertNoteRef (Para ils  : xs) = Para  (notemarkerXml : ils) : xs +  let insertNoteRef (Plain ils : xs) = Plain (notemarkerXml : Space : ils) : xs +      insertNoteRef (Para ils  : xs) = Para  (notemarkerXml : Space : ils) : xs        insertNoteRef xs               = Para [notemarkerXml] : xs    oldListLevel <- gets stListLevel    oldParaProperties <- gets stParaProperties diff --git a/src/Text/Pandoc/Writers/DokuWiki.hs b/src/Text/Pandoc/Writers/DokuWiki.hs index e7dbd7e2a..b68c46c7e 100644 --- a/src/Text/Pandoc/Writers/DokuWiki.hs +++ b/src/Text/Pandoc/Writers/DokuWiki.hs @@ -39,7 +39,6 @@ DokuWiki:  <https://www.dokuwiki.org/dokuwiki>  -}  module Text.Pandoc.Writers.DokuWiki ( writeDokuWiki ) where -import Prelude  import Text.Pandoc.Definition  import Text.Pandoc.Options ( WriterOptions(                                  writerTableOfContents diff --git a/src/Text/Pandoc/Writers/EPUB.hs b/src/Text/Pandoc/Writers/EPUB.hs index 2698ea4be..42f3d5e57 100644 --- a/src/Text/Pandoc/Writers/EPUB.hs +++ b/src/Text/Pandoc/Writers/EPUB.hs @@ -29,7 +29,6 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA  Conversion of 'Pandoc' documents to EPUB.  -}  module Text.Pandoc.Writers.EPUB ( writeEPUB ) where -import Prelude  import Data.IORef ( IORef, newIORef, readIORef, modifyIORef )  import qualified Data.Map as M  import Data.Maybe ( fromMaybe, catMaybes ) @@ -817,7 +816,8 @@ transformTag :: WriterOptions               -> Tag String               -> IO (Tag String)  transformTag opts mediaRef tag@(TagOpen name attr) -  | name `elem` ["video", "source", "img", "audio"] = do +  | name `elem` ["video", "source", "img", "audio"] && +    lookup "data-external" attr == Nothing = do    let src = fromAttrib "src" tag    let poster = fromAttrib "poster" tag    newsrc <- modifyMediaRef opts mediaRef src diff --git a/src/Text/Pandoc/Writers/FB2.hs b/src/Text/Pandoc/Writers/FB2.hs index f65f26dd6..31fa4bee8 100644 --- a/src/Text/Pandoc/Writers/FB2.hs +++ b/src/Text/Pandoc/Writers/FB2.hs @@ -27,7 +27,6 @@ FictionBook is an XML-based e-book format. For more information see:  -}  module Text.Pandoc.Writers.FB2 (writeFB2)  where -import Prelude  import Control.Monad.State (StateT, evalStateT, get, modify)  import Control.Monad.State (liftM, liftM2, liftIO)  import Data.ByteString.Base64 (encode) diff --git a/src/Text/Pandoc/Writers/HTML.hs b/src/Text/Pandoc/Writers/HTML.hs index fb52256b3..7e3f1c65a 100644 --- a/src/Text/Pandoc/Writers/HTML.hs +++ b/src/Text/Pandoc/Writers/HTML.hs @@ -30,8 +30,8 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA  Conversion of 'Pandoc' documents to HTML.  -}  module Text.Pandoc.Writers.HTML ( writeHtml , writeHtmlString ) where -import Prelude  import Text.Pandoc.Definition +import Text.Pandoc.Compat.Monoid ((<>))  import Text.Pandoc.Shared  import Text.Pandoc.Writers.Shared  import Text.Pandoc.Options @@ -541,6 +541,9 @@ blockToHtml opts (OrderedList (startnum, numstyle, _) lst) = do    let attribs = (if startnum /= 1                     then [A.start $ toValue startnum]                     else []) ++ +                (if numstyle == Example +                    then [A.class_ "example"] +                    else []) ++                  (if numstyle /= DefaultStyle                     then if writerHtml5 opts                             then [A.type_ $ diff --git a/src/Text/Pandoc/Writers/Haddock.hs b/src/Text/Pandoc/Writers/Haddock.hs index 884a0b318..5df6786ac 100644 --- a/src/Text/Pandoc/Writers/Haddock.hs +++ b/src/Text/Pandoc/Writers/Haddock.hs @@ -31,7 +31,6 @@ Conversion of 'Pandoc' documents to haddock markup.  Haddock:  <http://www.haskell.org/haddock/doc/html/>  -}  module Text.Pandoc.Writers.Haddock (writeHaddock) where -import Prelude  import Text.Pandoc.Definition  import Text.Pandoc.Templates (renderTemplate')  import Text.Pandoc.Shared @@ -328,8 +327,8 @@ inlineToHaddock _ (RawInline f str)  inlineToHaddock _ (LineBreak) = return cr  inlineToHaddock _ Space = return space  inlineToHaddock opts (Cite _ lst) = inlineListToHaddock opts lst -inlineToHaddock opts (Link txt (src, _)) = do -  linktext <- inlineListToHaddock opts txt +inlineToHaddock _opts (Link txt (src, _)) = do +  let linktext = text $ escapeString $ stringify txt    let useAuto = isURI src &&                  case txt of                        [Str s] | escapeURI s == src -> True diff --git a/src/Text/Pandoc/Writers/ICML.hs b/src/Text/Pandoc/Writers/ICML.hs index 3bb179353..95ea0c643 100644 --- a/src/Text/Pandoc/Writers/ICML.hs +++ b/src/Text/Pandoc/Writers/ICML.hs @@ -14,9 +14,9 @@ InCopy is the companion word-processor to Adobe InDesign and ICML documents can  into InDesign with File -> Place.  -}  module Text.Pandoc.Writers.ICML (writeICML) where -import Prelude  import Text.Pandoc.Definition  import Text.Pandoc.XML +import Text.Pandoc.Readers.TeXMath (texMathToInlines)  import Text.Pandoc.Writers.Shared  import Text.Pandoc.Shared (splitBy)  import Text.Pandoc.Options @@ -411,7 +411,8 @@ inlineToICML opts style (Cite _ lst) = inlinesToICML opts style lst  inlineToICML _    style (Code _ str) = charStyle (codeName:style) $ text $ escapeStringForXML str  inlineToICML _    style Space = charStyle style space  inlineToICML _ style LineBreak = charStyle style $ text lineSeparator -inlineToICML _ style (Math _ str) = charStyle style $ text $ escapeStringForXML str --InDesign doesn't really do math +inlineToICML opts style (Math mt str) = +  cat <$> mapM (inlineToICML opts style) (texMathToInlines mt str)  inlineToICML _ _ (RawInline f str)    | f == Format "icml" = return $ text str    | otherwise          = return empty diff --git a/src/Text/Pandoc/Writers/LaTeX.hs b/src/Text/Pandoc/Writers/LaTeX.hs index 97104c4dc..e9a2e0a56 100644 --- a/src/Text/Pandoc/Writers/LaTeX.hs +++ b/src/Text/Pandoc/Writers/LaTeX.hs @@ -30,7 +30,6 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA  Conversion of 'Pandoc' format into LaTeX.  -}  module Text.Pandoc.Writers.LaTeX ( writeLaTeX ) where -import Prelude  import Text.Pandoc.Definition  import Text.Pandoc.Walk  import Text.Pandoc.Shared @@ -42,7 +41,7 @@ import Network.URI ( isURI, unEscapeString )  import Data.Aeson (object, (.=))  import Data.List ( (\\), isInfixOf, stripPrefix, intercalate, intersperse, nub, nubBy )  import Data.Char ( toLower, isPunctuation, isAscii, isLetter, isDigit, ord ) -import Data.Maybe ( fromMaybe ) +import Data.Maybe ( fromMaybe, isJust )  import qualified Data.Text as T  import Control.Applicative ((<|>))  import Control.Monad.State @@ -147,6 +146,7 @@ pandocToLaTeX options (Pandoc meta blocks) = do    titleMeta <- stringToLaTeX TextString $ stringify $ docTitle meta    authorsMeta <- mapM (stringToLaTeX TextString . stringify) $ docAuthors meta    let docLangs = nub $ query (extract "lang") blocks +  let hasStringValue x = isJust (getField x metadata :: Maybe String)    let context  =  defField "toc" (writerTableOfContents options) $                    defField "toc-depth" (show (writerTOCDepth options -                                                if stBook st @@ -184,6 +184,8 @@ pandocToLaTeX options (Pandoc meta blocks) = do                    -- set lang to something so polyglossia/babel is included                    defField "lang" (if null docLangs then ""::String else "en") $                    defField "otherlangs" docLangs $ +                  defField "colorlinks" (any hasStringValue +                           ["citecolor", "urlcolor", "linkcolor", "toccolor"]) $                    defField "dir" (if (null $ query (extract "dir") blocks)                                       then ""::String                                       else "ltr") $ diff --git a/src/Text/Pandoc/Writers/Man.hs b/src/Text/Pandoc/Writers/Man.hs index d6fc0646b..6b1e42394 100644 --- a/src/Text/Pandoc/Writers/Man.hs +++ b/src/Text/Pandoc/Writers/Man.hs @@ -29,7 +29,6 @@ Conversion of 'Pandoc' documents to groff man page format.  -}  module Text.Pandoc.Writers.Man ( writeMan) where -import Prelude  import Text.Pandoc.Definition  import Text.Pandoc.Templates  import Text.Pandoc.Shared diff --git a/src/Text/Pandoc/Writers/Markdown.hs b/src/Text/Pandoc/Writers/Markdown.hs index e37e84c4f..cd9c26289 100644 --- a/src/Text/Pandoc/Writers/Markdown.hs +++ b/src/Text/Pandoc/Writers/Markdown.hs @@ -31,7 +31,6 @@ Conversion of 'Pandoc' documents to markdown-formatted plain text.  Markdown:  <http://daringfireball.net/projects/markdown/>  -}  module Text.Pandoc.Writers.Markdown (writeMarkdown, writePlain) where -import Prelude  import Text.Pandoc.Definition  import Text.Pandoc.Walk  import Text.Pandoc.Templates (renderTemplate') diff --git a/src/Text/Pandoc/Writers/MediaWiki.hs b/src/Text/Pandoc/Writers/MediaWiki.hs index 2735d2721..2b7c47e24 100644 --- a/src/Text/Pandoc/Writers/MediaWiki.hs +++ b/src/Text/Pandoc/Writers/MediaWiki.hs @@ -30,7 +30,6 @@ Conversion of 'Pandoc' documents to MediaWiki markup.  MediaWiki:  <http://www.mediawiki.org/wiki/MediaWiki>  -}  module Text.Pandoc.Writers.MediaWiki ( writeMediaWiki ) where -import Prelude  import Text.Pandoc.Definition  import Text.Pandoc.Options  import Text.Pandoc.Shared diff --git a/src/Text/Pandoc/Writers/Native.hs b/src/Text/Pandoc/Writers/Native.hs index 80694d74a..2343ff1a8 100644 --- a/src/Text/Pandoc/Writers/Native.hs +++ b/src/Text/Pandoc/Writers/Native.hs @@ -34,7 +34,6 @@ metadata.  -}  module Text.Pandoc.Writers.Native ( writeNative )  where -import Prelude  import Text.Pandoc.Options ( WriterOptions(..) )  import Data.List ( intersperse )  import Text.Pandoc.Definition diff --git a/src/Text/Pandoc/Writers/ODT.hs b/src/Text/Pandoc/Writers/ODT.hs index 6947ef396..922a3a785 100644 --- a/src/Text/Pandoc/Writers/ODT.hs +++ b/src/Text/Pandoc/Writers/ODT.hs @@ -29,7 +29,6 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA  Conversion of 'Pandoc' documents to ODT.  -}  module Text.Pandoc.Writers.ODT ( writeODT ) where -import Prelude  import Data.IORef  import Data.List ( isPrefixOf )  import Data.Maybe ( fromMaybe ) diff --git a/src/Text/Pandoc/Writers/OPML.hs b/src/Text/Pandoc/Writers/OPML.hs index ecf6799f5..519136861 100644 --- a/src/Text/Pandoc/Writers/OPML.hs +++ b/src/Text/Pandoc/Writers/OPML.hs @@ -29,7 +29,6 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA  Conversion of 'Pandoc' documents to OPML XML.  -}  module Text.Pandoc.Writers.OPML ( writeOPML) where -import Prelude  import Text.Pandoc.Definition  import Text.Pandoc.XML  import Text.Pandoc.Writers.Shared diff --git a/src/Text/Pandoc/Writers/OpenDocument.hs b/src/Text/Pandoc/Writers/OpenDocument.hs index 5d7f10bdd..7ee87f4af 100644 --- a/src/Text/Pandoc/Writers/OpenDocument.hs +++ b/src/Text/Pandoc/Writers/OpenDocument.hs @@ -30,7 +30,6 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA  Conversion of 'Pandoc' documents to OpenDocument XML.  -}  module Text.Pandoc.Writers.OpenDocument ( writeOpenDocument ) where -import Prelude  import Text.Pandoc.Definition  import Text.Pandoc.Options  import Text.Pandoc.XML @@ -192,8 +191,7 @@ writeOpenDocument opts (Pandoc meta blocks) =        listStyle (n,l) = inTags True "text:list-style"                            [("style:name", "L" ++ show n)] (vcat l)        listStyles  = map listStyle (stListStyles s) -      automaticStyles = inTagsIndented "office:automatic-styles" $ vcat $ -                          reverse $ styles ++ listStyles +      automaticStyles = vcat $ reverse $ styles ++ listStyles        context = defField "body" body                $ defField "automatic-styles" (render' automaticStyles)                $ metadata diff --git a/src/Text/Pandoc/Writers/Org.hs b/src/Text/Pandoc/Writers/Org.hs index 9e7894bed..1b0ab387f 100644 --- a/src/Text/Pandoc/Writers/Org.hs +++ b/src/Text/Pandoc/Writers/Org.hs @@ -32,7 +32,6 @@ Conversion of 'Pandoc' documents to Emacs Org-Mode.  Org-Mode:  <http://orgmode.org>  -}  module Text.Pandoc.Writers.Org ( writeOrg) where -import Prelude  import Text.Pandoc.Definition  import Text.Pandoc.Options  import Text.Pandoc.Shared diff --git a/src/Text/Pandoc/Writers/RST.hs b/src/Text/Pandoc/Writers/RST.hs index cf6fe38e9..334619880 100644 --- a/src/Text/Pandoc/Writers/RST.hs +++ b/src/Text/Pandoc/Writers/RST.hs @@ -31,7 +31,6 @@ Conversion of 'Pandoc' documents to reStructuredText.  reStructuredText:  <http://docutils.sourceforge.net/rst.html>  -}  module Text.Pandoc.Writers.RST ( writeRST ) where -import Prelude  import Text.Pandoc.Definition  import Text.Pandoc.Options  import Text.Pandoc.Shared diff --git a/src/Text/Pandoc/Writers/RTF.hs b/src/Text/Pandoc/Writers/RTF.hs index ec289e7a4..9eb02ad02 100644 --- a/src/Text/Pandoc/Writers/RTF.hs +++ b/src/Text/Pandoc/Writers/RTF.hs @@ -28,7 +28,6 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA  Conversion of 'Pandoc' documents to RTF (rich text format).  -}  module Text.Pandoc.Writers.RTF ( writeRTF, writeRTFWithEmbeddedImages ) where -import Prelude  import Text.Pandoc.Definition  import Text.Pandoc.Options  import Text.Pandoc.Shared diff --git a/src/Text/Pandoc/Writers/Shared.hs b/src/Text/Pandoc/Writers/Shared.hs index 2c9d077cc..d94dbac46 100644 --- a/src/Text/Pandoc/Writers/Shared.hs +++ b/src/Text/Pandoc/Writers/Shared.hs @@ -37,7 +37,6 @@ module Text.Pandoc.Writers.Shared (                       , fixDisplayMath                       )  where -import Prelude  import Text.Pandoc.Definition  import Text.Pandoc.Pretty  import Text.Pandoc.XML (escapeStringForXML) diff --git a/src/Text/Pandoc/Writers/Texinfo.hs b/src/Text/Pandoc/Writers/Texinfo.hs index 119c45155..2325d1425 100644 --- a/src/Text/Pandoc/Writers/Texinfo.hs +++ b/src/Text/Pandoc/Writers/Texinfo.hs @@ -29,7 +29,6 @@ Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA  Conversion of 'Pandoc' format into Texinfo.  -}  module Text.Pandoc.Writers.Texinfo ( writeTexinfo ) where -import Prelude  import Text.Pandoc.Definition  import Text.Pandoc.Options  import Text.Pandoc.Shared diff --git a/src/Text/Pandoc/Writers/Textile.hs b/src/Text/Pandoc/Writers/Textile.hs index 6322ce232..dbc9eb40a 100644 --- a/src/Text/Pandoc/Writers/Textile.hs +++ b/src/Text/Pandoc/Writers/Textile.hs @@ -30,7 +30,6 @@ Conversion of 'Pandoc' documents to Textile markup.  Textile:  <http://thresholdstate.com/articles/4312/the-textile-reference-manual>  -}  module Text.Pandoc.Writers.Textile ( writeTextile ) where -import Prelude  import Text.Pandoc.Definition  import Text.Pandoc.Options  import Text.Pandoc.Shared diff --git a/src/Text/Pandoc/XML.hs b/src/Text/Pandoc/XML.hs index f53251a1f..caa13f177 100644 --- a/src/Text/Pandoc/XML.hs +++ b/src/Text/Pandoc/XML.hs @@ -36,7 +36,6 @@ module Text.Pandoc.XML ( escapeCharForXML,                           toEntities,                           fromEntities ) where -import Prelude  import Text.Pandoc.Pretty  import Data.Char (ord, isAscii, isSpace)  import Text.Pandoc.Compat.TagSoupEntity (lookupEntity) | 
