blob: d5b8f2c5dbd814304bbf6406a9deff7a6fc42a73 (
plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
|
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE FlexibleInstances #-}
{- |
Module : Text.Pandoc.Lua.Orphans
Copyright : © 2012-2021 John MacFarlane
© 2017-2021 Albert Krewinkel
License : GNU GPL, version 2 or above
Maintainer : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
Stability : alpha
Orphan instances for Lua's Pushable and Peekable type classes.
-}
module Text.Pandoc.Lua.Orphans () where
import Data.Version (Version)
import HsLua
import HsLua.Module.Version (peekVersionFuzzy)
import Text.Pandoc.Definition
import Text.Pandoc.Lua.Marshal.AST
import Text.Pandoc.Lua.Marshal.CommonState ()
import Text.Pandoc.Lua.Marshal.Context ()
import Text.Pandoc.Lua.Marshal.PandocError()
import Text.Pandoc.Lua.Marshal.ReaderOptions ()
import Text.Pandoc.Lua.Marshal.Sources (pushSources)
import Text.Pandoc.Lua.ErrorConversion ()
import Text.Pandoc.Sources (Sources)
instance Pushable Pandoc where
push = pushPandoc
instance Pushable Meta where
push = pushMeta
instance Pushable MetaValue where
push = pushMetaValue
instance Pushable Block where
push = pushBlock
instance {-# OVERLAPPING #-} Pushable [Block] where
push = pushBlocks
instance Pushable Alignment where
push = pushString . show
instance Pushable CitationMode where
push = pushCitationMode
instance Pushable Format where
push = pushFormat
instance Pushable ListNumberDelim where
push = pushString . show
instance Pushable ListNumberStyle where
push = pushString . show
instance Pushable MathType where
push = pushMathType
instance Pushable QuoteType where
push = pushQuoteType
instance Pushable Cell where
push = pushCell
instance Peekable Cell where
peek = forcePeek . peekCell
instance Pushable Inline where
push = pushInline
instance {-# OVERLAPPING #-} Pushable [Inline] where
push = pushInlines
instance Pushable Citation where
push = pushCitation
instance Pushable Row where
push = pushRow
instance Pushable TableBody where
push = pushTableBody
instance Pushable TableFoot where
push = pushTableFoot
instance Pushable TableHead where
push = pushTableHead
-- These instances exist only for testing. It's a hack to avoid making
-- the marshalling modules public.
instance Peekable Inline where
peek = forcePeek . peekInline
instance Peekable Block where
peek = forcePeek . peekBlock
instance Peekable Meta where
peek = forcePeek . peekMeta
instance Peekable Pandoc where
peek = forcePeek . peekPandoc
instance Peekable Row where
peek = forcePeek . peekRow
instance Peekable Version where
peek = forcePeek . peekVersionFuzzy
instance {-# OVERLAPPING #-} Peekable Attr where
peek = forcePeek . peekAttr
instance Pushable Sources where
push = pushSources
|