File tree Expand file tree Collapse file tree 4 files changed +7
-9
lines changed Expand file tree Collapse file tree 4 files changed +7
-9
lines changed Original file line number Diff line number Diff line change
1
+ {-# LANGUAGE CPP #-}
1
2
{-# LANGUAGE LambdaCase #-}
2
3
{-# LANGUAGE OverloadedStrings #-}
3
4
{-|
@@ -19,6 +20,10 @@ import Data.ByteString.Lazy (interact)
19
20
import Options.Applicative
20
21
import Text.Pandoc.AST.Migrator (ASTVersion (.. ), migrateJSON )
21
22
23
+ #if !MIN_VERSION_base(4,11,0)
24
+ import Data.Semigroup (Semigroup (.. ))
25
+ #endif
26
+
22
27
-- | Migration parameters
23
28
data Migration = Migration
24
29
{ initialVersion :: ASTVersion
Original file line number Diff line number Diff line change @@ -7,7 +7,7 @@ Maintainer : Albert Krewinkel <albert@zeitkraut.de>
7
7
Stability : alpha
8
8
Portability : portable
9
9
10
- Migrate from or to older AST versions.
10
+ Migrate from or to older API versions.
11
11
-}
12
12
module Text.Pandoc.AST.Migrator
13
13
( ASTVersion (.. )
@@ -27,6 +27,7 @@ import Text.Pandoc.AST.V1_21.Down (migrateDownFromV1_21)
27
27
import Text.Pandoc.AST.V1_21.Up (migrateUpToV1_22 )
28
28
import Text.Pandoc.AST.V1_22.Down (migrateDownFromV1_22 )
29
29
30
+ -- | Supported pandoc API versions.
30
31
data ASTVersion
31
32
= V1_20 -- ^ Version 1.20
32
33
| V1_21 -- ^ Version 1.21
Original file line number Diff line number Diff line change @@ -20,10 +20,6 @@ import Text.Pandoc.AST.V1_21.Definition
20
20
import qualified Text.Pandoc.AST.V1_22.Definition as V1_22
21
21
import qualified Data.Map as M
22
22
23
- #if !MIN_VERSION_base(4,11,0)
24
- import Data.Semigroup (Semigroup (.. ))
25
- #endif
26
-
27
23
migrateDown :: Pandoc -> V1_22. Pandoc
28
24
migrateDown = migrateUpToV1_22
29
25
Original file line number Diff line number Diff line change @@ -20,10 +20,6 @@ import Text.Pandoc.AST.V1_22.Definition
20
20
import qualified Text.Pandoc.AST.V1_21.Definition as V1_21
21
21
import qualified Data.Map as M
22
22
23
- #if !MIN_VERSION_base(4,11,0)
24
- import Data.Semigroup (Semigroup (.. ))
25
- #endif
26
-
27
23
migrateDown :: Pandoc -> V1_21. Pandoc
28
24
migrateDown = migrateDownFromV1_22
29
25
You can’t perform that action at this time.
0 commit comments