|
| 1 | +{-# LANGUAGE CPP #-} |
| 2 | +{-# LANGUAGE LambdaCase #-} |
| 3 | +{- | |
| 4 | +Module : Text.Pandoc.AST.V1_22.Down |
| 5 | +Copyright : © 2020 Albert Krewinkel |
| 6 | +License : MIT |
| 7 | +
|
| 8 | +Maintainer : Albert Krewinkel <albert@zeitkraut.de> |
| 9 | +Stability : alpha |
| 10 | +Portability : portable |
| 11 | +
|
| 12 | +Migrate from V1.22 to V1.21. |
| 13 | +-} |
| 14 | +module Text.Pandoc.AST.V1_22.Down |
| 15 | + ( migrateDownFromV1_22 |
| 16 | + , migrateDown |
| 17 | + ) where |
| 18 | + |
| 19 | +import Text.Pandoc.AST.V1_22.Definition |
| 20 | +import qualified Text.Pandoc.AST.V1_21.Definition as V1_21 |
| 21 | +import qualified Data.Map as M |
| 22 | + |
| 23 | +#if !MIN_VERSION_base(4,11,0) |
| 24 | +import Data.Semigroup (Semigroup(..)) |
| 25 | +#endif |
| 26 | + |
| 27 | +migrateDown :: Pandoc -> V1_21.Pandoc |
| 28 | +migrateDown = migrateDownFromV1_22 |
| 29 | + |
| 30 | +migrateDownFromV1_22 :: Pandoc -> V1_21.Pandoc |
| 31 | +migrateDownFromV1_22 (Pandoc meta blocks) = |
| 32 | + V1_21.Pandoc (migrateMeta meta) (map migrateBlock blocks) |
| 33 | + |
| 34 | +migrateMeta :: Meta -> V1_21.Meta |
| 35 | +migrateMeta = V1_21.Meta . M.map migrateMetaValue . unMeta |
| 36 | + |
| 37 | +migrateBlock :: Block -> V1_21.Block |
| 38 | +migrateBlock = \case |
| 39 | + BlockQuote blks -> V1_21.BlockQuote $ migrateBlocks blks |
| 40 | + BulletList items -> V1_21.BulletList $ migrateItems items |
| 41 | + CodeBlock attr text -> V1_21.CodeBlock attr text |
| 42 | + DefinitionList defItems -> V1_21.DefinitionList |
| 43 | + $ map migrateDefItem defItems |
| 44 | + Div attr blks -> V1_21.Div attr $ migrateBlocks blks |
| 45 | + Header lvl attr inlns -> V1_21.Header lvl attr |
| 46 | + $ migrateInlines inlns |
| 47 | + HorizontalRule -> V1_21.HorizontalRule |
| 48 | + LineBlock lines' -> V1_21.LineBlock $ map migrateInlines lines' |
| 49 | + Null -> V1_21.Null |
| 50 | + OrderedList listAttr items -> V1_21.OrderedList |
| 51 | + (migrateListAttributes listAttr) |
| 52 | + (migrateItems items) |
| 53 | + Para inlns -> V1_21.Para $ migrateInlines inlns |
| 54 | + Plain inlns -> V1_21.Plain $ migrateInlines inlns |
| 55 | + RawBlock f text -> V1_21.RawBlock (migrateFormat f) text |
| 56 | + Table as capt col th tb tf -> V1_21.Table as |
| 57 | + (migrateCaption capt) |
| 58 | + (map migrateColSpec col) |
| 59 | + (migrateTableHead th) |
| 60 | + (map migrateTableBody tb) |
| 61 | + (migrateTableFoot tf) |
| 62 | + where |
| 63 | + migrateItems = map migrateBlocks |
| 64 | + migrateDefItem (def, items) = (migrateInlines def, migrateItems items) |
| 65 | + |
| 66 | +migrateBlocks :: [Block] -> [V1_21.Block] |
| 67 | +migrateBlocks = map migrateBlock |
| 68 | + |
| 69 | +migrateInlines :: [Inline] -> [V1_21.Inline] |
| 70 | +migrateInlines = map migrateInline |
| 71 | + |
| 72 | +migrateMetaValue :: MetaValue -> V1_21.MetaValue |
| 73 | +migrateMetaValue = \case |
| 74 | + MetaBlocks blocks -> V1_21.MetaBlocks $ map migrateBlock blocks |
| 75 | + MetaBool b -> V1_21.MetaBool b |
| 76 | + MetaInlines inlines -> V1_21.MetaInlines $ map migrateInline inlines |
| 77 | + MetaList vs -> V1_21.MetaList $ map migrateMetaValue vs |
| 78 | + MetaMap metamap -> V1_21.MetaMap $ M.map migrateMetaValue metamap |
| 79 | + MetaString s -> V1_21.MetaString s |
| 80 | + |
| 81 | +migrateAlignment :: Alignment -> V1_21.Alignment |
| 82 | +migrateAlignment = \case |
| 83 | + AlignLeft -> V1_21.AlignLeft |
| 84 | + AlignRight -> V1_21.AlignRight |
| 85 | + AlignCenter -> V1_21.AlignCenter |
| 86 | + AlignDefault -> V1_21.AlignDefault |
| 87 | + |
| 88 | +migrateColSpec :: ColSpec -> V1_21.ColSpec |
| 89 | +migrateColSpec (align, colwidth) = |
| 90 | + let colwidth' = case colwidth of |
| 91 | + ColWidth d -> V1_21.ColWidth d |
| 92 | + ColWidthDefault -> V1_21.ColWidthDefault |
| 93 | + in (migrateAlignment align, colwidth') |
| 94 | + |
| 95 | +migrateCaption :: Caption -> V1_21.Caption |
| 96 | +migrateCaption (Caption short long) = |
| 97 | + V1_21.Caption (fmap migrateInlines short) (migrateBlocks long) |
| 98 | + |
| 99 | +migrateTableBody :: TableBody -> V1_21.TableBody |
| 100 | +migrateTableBody (TableBody attr (RowHeadColumns rhc) intHead rows) = |
| 101 | + V1_21.TableBody attr |
| 102 | + (V1_21.RowHeadColumns rhc) |
| 103 | + (map migrateRow intHead) |
| 104 | + (map migrateRow rows) |
| 105 | + |
| 106 | +migrateTableFoot :: TableFoot -> V1_21.TableFoot |
| 107 | +migrateTableFoot (TableFoot attr rows) = |
| 108 | + V1_21.TableFoot attr (map migrateRow rows) |
| 109 | + |
| 110 | +migrateTableHead :: TableHead -> V1_21.TableHead |
| 111 | +migrateTableHead (TableHead attr rows) = |
| 112 | + V1_21.TableHead attr (map migrateRow rows) |
| 113 | + |
| 114 | +migrateRow :: Row -> V1_21.Row |
| 115 | +migrateRow (Row attr cells) = |
| 116 | + V1_21.Row attr (map migrateCell cells) |
| 117 | + |
| 118 | +migrateCell :: Cell -> V1_21.Cell |
| 119 | +migrateCell (Cell attr align (RowSpan rs) (ColSpan cs) blks) = |
| 120 | + V1_21.Cell |
| 121 | + attr |
| 122 | + (migrateAlignment align) |
| 123 | + (V1_21.RowSpan rs) |
| 124 | + (V1_21.ColSpan cs) |
| 125 | + (migrateBlocks blks) |
| 126 | + |
| 127 | +migrateListNumberDelim :: ListNumberDelim -> V1_21.ListNumberDelim |
| 128 | +migrateListNumberDelim = \case |
| 129 | + DefaultDelim -> V1_21.DefaultDelim |
| 130 | + Period -> V1_21.Period |
| 131 | + OneParen -> V1_21.OneParen |
| 132 | + TwoParens -> V1_21.TwoParens |
| 133 | + |
| 134 | +migrateListNumberStyle :: ListNumberStyle -> V1_21.ListNumberStyle |
| 135 | +migrateListNumberStyle = \case |
| 136 | + DefaultStyle -> V1_21.DefaultStyle |
| 137 | + Example -> V1_21.Example |
| 138 | + Decimal -> V1_21.Decimal |
| 139 | + LowerRoman -> V1_21.LowerRoman |
| 140 | + UpperRoman -> V1_21.UpperRoman |
| 141 | + LowerAlpha -> V1_21.LowerAlpha |
| 142 | + UpperAlpha -> V1_21.UpperAlpha |
| 143 | + |
| 144 | +migrateListAttributes :: ListAttributes -> V1_21.ListAttributes |
| 145 | +migrateListAttributes (n, style, delim) = |
| 146 | + (n, migrateListNumberStyle style, migrateListNumberDelim delim) |
| 147 | + |
| 148 | +migrateFormat :: Format -> V1_21.Format |
| 149 | +migrateFormat (Format f) = V1_21.Format f |
| 150 | + |
| 151 | +migrateQuoteType :: QuoteType -> V1_21.QuoteType |
| 152 | +migrateQuoteType = \case |
| 153 | + SingleQuote -> V1_21.SingleQuote |
| 154 | + DoubleQuote -> V1_21.DoubleQuote |
| 155 | + |
| 156 | +migrateMathType :: MathType -> V1_21.MathType |
| 157 | +migrateMathType = \case |
| 158 | + DisplayMath -> V1_21.DisplayMath |
| 159 | + InlineMath -> V1_21.InlineMath |
| 160 | + |
| 161 | +migrateInline :: Inline -> V1_21.Inline |
| 162 | +migrateInline = \case |
| 163 | + Cite citations inlns -> V1_21.Cite (migrateCitations citations) $ migrateInlines inlns |
| 164 | + Code attr text -> V1_21.Code attr text |
| 165 | + Emph inlns -> V1_21.Emph $ migrateInlines inlns |
| 166 | + Image attr inlns tgt -> V1_21.Image attr (migrateInlines inlns) tgt |
| 167 | + LineBreak -> V1_21.LineBreak |
| 168 | + Link attr inlns tgt -> V1_21.Link attr (migrateInlines inlns) tgt |
| 169 | + Math mathType text -> V1_21.Math (migrateMathType mathType) text |
| 170 | + Note blks -> V1_21.Note $ migrateBlocks blks |
| 171 | + Quoted qtype inlns -> V1_21.Quoted (migrateQuoteType qtype) $ migrateInlines inlns |
| 172 | + RawInline f text -> V1_21.RawInline (migrateFormat f) text |
| 173 | + SmallCaps inlns -> V1_21.SmallCaps $ migrateInlines inlns |
| 174 | + SoftBreak -> V1_21.SoftBreak |
| 175 | + Space -> V1_21.Space |
| 176 | + Span attr inlns -> V1_21.Span attr $ migrateInlines inlns |
| 177 | + Str text -> V1_21.Str text |
| 178 | + Strikeout inlns -> V1_21.Strikeout $ migrateInlines inlns |
| 179 | + Strong inlns -> V1_21.Strong $ migrateInlines inlns |
| 180 | + Subscript inlns -> V1_21.Subscript $ migrateInlines inlns |
| 181 | + Superscript inlns -> V1_21.Superscript $ migrateInlines inlns |
| 182 | + Underline inlns -> V1_21.Underline $ migrateInlines inlns |
| 183 | + where |
| 184 | + migrateCitations = map migrateCitation |
| 185 | + |
| 186 | +migrateCitation :: Citation -> V1_21.Citation |
| 187 | +migrateCitation citation = V1_21.Citation |
| 188 | + (citationId citation) |
| 189 | + (map migrateInline $ citationPrefix citation) |
| 190 | + (map migrateInline $ citationSuffix citation) |
| 191 | + (migrateCitationMode $ citationMode citation) |
| 192 | + (citationNoteNum citation) |
| 193 | + (citationHash citation) |
| 194 | + |
| 195 | +migrateCitationMode :: CitationMode -> V1_21.CitationMode |
| 196 | +migrateCitationMode = \case |
| 197 | + AuthorInText -> V1_21.AuthorInText |
| 198 | + NormalCitation -> V1_21.NormalCitation |
| 199 | + SuppressAuthor -> V1_21.SuppressAuthor |
0 commit comments