{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE FlexibleInstances    #-}
{- |
   Module      : Text.Pandoc.Lua.Orphans
   Copyright   : © 2012-2024 John MacFarlane
                 © 2017-2024 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.Sources (Sources)

instance Pushable Pandoc where
  push :: forall e. LuaError e => Pandoc -> LuaE e ()
push = Pusher e Pandoc
forall e. LuaError e => Pandoc -> LuaE e ()
pushPandoc

instance Pushable Meta where
  push :: forall e. LuaError e => Meta -> LuaE e ()
push = Pusher e Meta
forall e. LuaError e => Meta -> LuaE e ()
pushMeta

instance Pushable MetaValue where
  push :: forall e. LuaError e => MetaValue -> LuaE e ()
push = Pusher e MetaValue
forall e. LuaError e => MetaValue -> LuaE e ()
pushMetaValue

instance Pushable Block where
  push :: forall e. LuaError e => Block -> LuaE e ()
push = Pusher e Block
forall e. LuaError e => Block -> LuaE e ()
pushBlock

instance {-# OVERLAPPING #-} Pushable [Block] where
  push :: forall e. LuaError e => [Block] -> LuaE e ()
push = Pusher e [Block]
forall e. LuaError e => [Block] -> LuaE e ()
pushBlocks

instance Pushable Alignment where
  push :: forall e. LuaError e => Alignment -> LuaE e ()
push = String -> LuaE e ()
forall e. String -> LuaE e ()
pushString (String -> LuaE e ())
-> (Alignment -> String) -> Alignment -> LuaE e ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Alignment -> String
forall a. Show a => a -> String
show

instance Pushable CitationMode where
  push :: forall e. LuaError e => CitationMode -> LuaE e ()
push = Pusher e CitationMode
forall e. Pusher e CitationMode
pushCitationMode

instance Pushable Format where
  push :: forall e. LuaError e => Format -> LuaE e ()
push = Pusher e Format
forall e. Pusher e Format
pushFormat

instance Pushable ListNumberDelim where
  push :: forall e. LuaError e => ListNumberDelim -> LuaE e ()
push = String -> LuaE e ()
forall e. String -> LuaE e ()
pushString (String -> LuaE e ())
-> (ListNumberDelim -> String) -> ListNumberDelim -> LuaE e ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ListNumberDelim -> String
forall a. Show a => a -> String
show

instance Pushable ListNumberStyle where
  push :: forall e. LuaError e => ListNumberStyle -> LuaE e ()
push = String -> LuaE e ()
forall e. String -> LuaE e ()
pushString (String -> LuaE e ())
-> (ListNumberStyle -> String) -> ListNumberStyle -> LuaE e ()
forall b c a. (b -> c) -> (a -> b) -> a -> c
. ListNumberStyle -> String
forall a. Show a => a -> String
show

instance Pushable MathType where
  push :: forall e. LuaError e => MathType -> LuaE e ()
push = Pusher e MathType
forall e. Pusher e MathType
pushMathType

instance Pushable QuoteType where
  push :: forall e. LuaError e => QuoteType -> LuaE e ()
push = Pusher e QuoteType
forall e. Pusher e QuoteType
pushQuoteType

instance Pushable Cell where
  push :: forall e. LuaError e => Cell -> LuaE e ()
push = Cell -> LuaE e ()
forall e. LuaError e => Cell -> LuaE e ()
pushCell

instance Pushable Inline where
  push :: forall e. LuaError e => Inline -> LuaE e ()
push = Pusher e Inline
forall e. LuaError e => Inline -> LuaE e ()
pushInline

instance {-# OVERLAPPING #-} Pushable [Inline] where
  push :: forall e. LuaError e => [Inline] -> LuaE e ()
push = Pusher e [Inline]
forall e. LuaError e => [Inline] -> LuaE e ()
pushInlines

instance Pushable Citation where
  push :: forall e. LuaError e => Citation -> LuaE e ()
push = Pusher e Citation
forall e. LuaError e => Citation -> LuaE e ()
pushCitation

instance Pushable Row where
  push :: forall e. LuaError e => Row -> LuaE e ()
push = Row -> LuaE e ()
forall e. LuaError e => Row -> LuaE e ()
pushRow

instance Pushable TableBody where
  push :: forall e. LuaError e => TableBody -> LuaE e ()
push = Pusher e TableBody
forall e. LuaError e => TableBody -> LuaE e ()
pushTableBody

instance Pushable TableFoot where
  push :: forall e. LuaError e => TableFoot -> LuaE e ()
push = TableFoot -> LuaE e ()
forall e. LuaError e => TableFoot -> LuaE e ()
pushTableFoot

instance Pushable TableHead where
  push :: forall e. LuaError e => TableHead -> LuaE e ()
push = TableHead -> LuaE e ()
forall e. LuaError e => TableHead -> LuaE e ()
pushTableHead

-- These instances exist only for testing. It's a hack to avoid making
-- the marshalling modules public.
instance Peekable Inline where
  safepeek :: forall e. LuaError e => Peeker e Inline
safepeek = Peeker e Inline
forall e. LuaError e => Peeker e Inline
peekInline

instance Peekable Block where
  safepeek :: forall e. LuaError e => Peeker e Block
safepeek = Peeker e Block
forall e. LuaError e => Peeker e Block
peekBlock

instance Peekable Cell where
  safepeek :: forall e. LuaError e => Peeker e Cell
safepeek = Peeker e Cell
forall e. LuaError e => Peeker e Cell
peekCell

instance Peekable Meta where
  safepeek :: forall e. LuaError e => Peeker e Meta
safepeek = Peeker e Meta
forall e. LuaError e => Peeker e Meta
peekMeta

instance Peekable Pandoc where
  safepeek :: forall e. LuaError e => Peeker e Pandoc
safepeek = Peeker e Pandoc
forall e. LuaError e => Peeker e Pandoc
peekPandoc

instance Peekable Row where
  safepeek :: forall e. LuaError e => Peeker e Row
safepeek = Peeker e Row
forall e. LuaError e => Peeker e Row
peekRow

instance Peekable Version where
  safepeek :: forall e. LuaError e => Peeker e Version
safepeek = Peeker e Version
forall e. LuaError e => Peeker e Version
peekVersionFuzzy

instance {-# OVERLAPPING #-} Peekable Attr where
  safepeek :: forall e. LuaError e => Peeker e Attr
safepeek = Peeker e Attr
forall e. LuaError e => Peeker e Attr
peekAttr

instance Pushable Sources where
  push :: forall e. LuaError e => Sources -> LuaE e ()
push = Pusher e Sources
forall e. LuaError e => Sources -> LuaE e ()
pushSources