{-# LANGUAGE OverloadedStrings    #-}
{- |
Copyright               : © 2021 Albert Krewinkel
SPDX-License-Identifier : MIT
Maintainer              : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>

Marshaling/unmarshaling functions and constructor for 'Citation' values.
-}
module Text.Pandoc.Lua.Marshal.Citation
  ( -- * Citation
    peekCitation
  , pushCitation
  , typeCitation
  , mkCitation
  ) where

import Control.Applicative (optional)
import Data.Maybe (fromMaybe)
import HsLua as Lua
import Text.Pandoc.Lua.Marshal.CitationMode (peekCitationMode, pushCitationMode)
import {-# SOURCE #-} Text.Pandoc.Lua.Marshal.Inline (peekInlinesFuzzy, pushInlines)
import Text.Pandoc.Definition (Citation (..))

-- | Pushes a Citation value as userdata object.
pushCitation :: LuaError e
             => Pusher e Citation
pushCitation :: Pusher e Citation
pushCitation = UDTypeWithList e (DocumentedFunction e) Citation Void
-> Pusher e Citation
forall e fn a itemtype.
LuaError e =>
UDTypeWithList e fn a itemtype -> a -> LuaE e ()
pushUD UDTypeWithList e (DocumentedFunction e) Citation Void
forall e. LuaError e => DocumentedType e Citation
typeCitation
{-# INLINE pushCitation #-}

-- | Retrieves a Citation value.
peekCitation :: LuaError e
             => Peeker e Citation
peekCitation :: Peeker e Citation
peekCitation = UDTypeWithList e (DocumentedFunction e) Citation Void
-> Peeker e Citation
forall e fn a itemtype.
LuaError e =>
UDTypeWithList e fn a itemtype -> Peeker e a
peekUD  UDTypeWithList e (DocumentedFunction e) Citation Void
forall e. LuaError e => DocumentedType e Citation
typeCitation
{-# INLINE peekCitation #-}

-- | Citation object type.
typeCitation :: LuaError e
             => DocumentedType e Citation
typeCitation :: DocumentedType e Citation
typeCitation = Name
-> [(Operation, DocumentedFunction e)]
-> [Member e (DocumentedFunction e) Citation]
-> DocumentedType e Citation
forall e a.
LuaError e =>
Name
-> [(Operation, DocumentedFunction e)]
-> [Member e (DocumentedFunction e) a]
-> DocumentedType e a
deftype Name
"Citation"
  [ Operation
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
forall e.
Operation
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
operation Operation
Eq (DocumentedFunction e -> (Operation, DocumentedFunction e))
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
forall a b. (a -> b) -> a -> b
$ (Maybe Citation -> Maybe Citation -> LuaE e Bool)
-> HsFnPrecursor
     e (Maybe Citation -> Maybe Citation -> LuaE e Bool)
forall a e. a -> HsFnPrecursor e a
lambda
    ### liftPure2 (\a b -> fromMaybe False ((==) <$> a <*> b))
    HsFnPrecursor e (Maybe Citation -> Maybe Citation -> LuaE e Bool)
-> Parameter e (Maybe Citation)
-> HsFnPrecursor e (Maybe Citation -> LuaE e Bool)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e (Maybe Citation)
-> Text -> Text -> Text -> Parameter e (Maybe Citation)
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter (Peek e Citation -> Peek e (Maybe Citation)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Peek e Citation -> Peek e (Maybe Citation))
-> (StackIndex -> Peek e Citation) -> Peeker e (Maybe Citation)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StackIndex -> Peek e Citation
forall e. LuaError e => Peeker e Citation
peekCitation) Text
"Citation" Text
"a" Text
""
    HsFnPrecursor e (Maybe Citation -> LuaE e Bool)
-> Parameter e (Maybe Citation) -> HsFnPrecursor e (LuaE e Bool)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e (Maybe Citation)
-> Text -> Text -> Text -> Parameter e (Maybe Citation)
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter (Peek e Citation -> Peek e (Maybe Citation)
forall (f :: * -> *) a. Alternative f => f a -> f (Maybe a)
optional (Peek e Citation -> Peek e (Maybe Citation))
-> (StackIndex -> Peek e Citation) -> Peeker e (Maybe Citation)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. StackIndex -> Peek e Citation
forall e. LuaError e => Peeker e Citation
peekCitation) Text
"Citation" Text
"b" Text
""
    HsFnPrecursor e (LuaE e Bool)
-> FunctionResults e Bool -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Bool -> Text -> Text -> FunctionResults e Bool
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Bool
forall e. Pusher e Bool
pushBool Text
"boolean" Text
"true iff the citations are equal"

  , Operation
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
forall e.
Operation
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
operation Operation
Tostring (DocumentedFunction e -> (Operation, DocumentedFunction e))
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
forall a b. (a -> b) -> a -> b
$ (Citation -> LuaE e String)
-> HsFnPrecursor e (Citation -> LuaE e String)
forall a e. a -> HsFnPrecursor e a
lambda
    ### liftPure show
    HsFnPrecursor e (Citation -> LuaE e String)
-> Parameter e Citation -> HsFnPrecursor e (LuaE e String)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> (StackIndex -> Peek e Citation)
-> Text -> Text -> Text -> Parameter e Citation
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter StackIndex -> Peek e Citation
forall e. LuaError e => Peeker e Citation
peekCitation Text
"Citation" Text
"citation" Text
""
    HsFnPrecursor e (LuaE e String)
-> FunctionResults e String -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e String -> Text -> Text -> FunctionResults e String
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e String
forall e. String -> LuaE e ()
pushString Text
"string" Text
"native Haskell representation"
  ]
  [ Name
-> Text
-> (Pusher e Text, Citation -> Text)
-> (Peeker e Text, Citation -> Text -> Citation)
-> Member e (DocumentedFunction e) Citation
forall e b a fn.
LuaError e =>
Name
-> Text
-> (Pusher e b, a -> b)
-> (Peeker e b, a -> b -> a)
-> Member e fn a
property Name
"id" Text
"citation ID / key"
      (Pusher e Text
forall e. Pusher e Text
pushText, Citation -> Text
citationId)
      (Peeker e Text
forall e. Peeker e Text
peekText, \Citation
citation Text
cid -> Citation
citation{ citationId :: Text
citationId = Text
cid })
  , Name
-> Text
-> (Pusher e CitationMode, Citation -> CitationMode)
-> (Peeker e CitationMode, Citation -> CitationMode -> Citation)
-> Member e (DocumentedFunction e) Citation
forall e b a fn.
LuaError e =>
Name
-> Text
-> (Pusher e b, a -> b)
-> (Peeker e b, a -> b -> a)
-> Member e fn a
property Name
"mode" Text
"citation mode"
      (Pusher e CitationMode
forall e. Pusher e CitationMode
pushCitationMode, Citation -> CitationMode
citationMode)
      (Peeker e CitationMode
forall e. Peeker e CitationMode
peekCitationMode, \Citation
citation CitationMode
mode -> Citation
citation{ citationMode :: CitationMode
citationMode = CitationMode
mode })
  , Name
-> Text
-> (Pusher e [Inline], Citation -> [Inline])
-> (Peeker e [Inline], Citation -> [Inline] -> Citation)
-> Member e (DocumentedFunction e) Citation
forall e b a fn.
LuaError e =>
Name
-> Text
-> (Pusher e b, a -> b)
-> (Peeker e b, a -> b -> a)
-> Member e fn a
property Name
"prefix" Text
"citation prefix"
      (Pusher e [Inline]
forall e. LuaError e => Pusher e [Inline]
pushInlines, Citation -> [Inline]
citationPrefix)
      (Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy, \Citation
citation [Inline]
prefix -> Citation
citation{ citationPrefix :: [Inline]
citationPrefix = [Inline]
prefix })
  , Name
-> Text
-> (Pusher e [Inline], Citation -> [Inline])
-> (Peeker e [Inline], Citation -> [Inline] -> Citation)
-> Member e (DocumentedFunction e) Citation
forall e b a fn.
LuaError e =>
Name
-> Text
-> (Pusher e b, a -> b)
-> (Peeker e b, a -> b -> a)
-> Member e fn a
property Name
"suffix" Text
"citation suffix"
      (Pusher e [Inline]
forall e. LuaError e => Pusher e [Inline]
pushInlines, Citation -> [Inline]
citationSuffix)
      (Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy, \Citation
citation [Inline]
suffix -> Citation
citation{ citationSuffix :: [Inline]
citationSuffix = [Inline]
suffix })
  , Name
-> Text
-> (Pusher e Int, Citation -> Int)
-> (Peeker e Int, Citation -> Int -> Citation)
-> Member e (DocumentedFunction e) Citation
forall e b a fn.
LuaError e =>
Name
-> Text
-> (Pusher e b, a -> b)
-> (Peeker e b, a -> b -> a)
-> Member e fn a
property Name
"note_num" Text
"note number"
      (Pusher e Int
forall a e. (Integral a, Show a) => a -> LuaE e ()
pushIntegral, Citation -> Int
citationNoteNum)
      (Peeker e Int
forall a e. (Integral a, Read a) => Peeker e a
peekIntegral, \Citation
citation Int
noteNum -> Citation
citation{ citationNoteNum :: Int
citationNoteNum = Int
noteNum })
  , Name
-> Text
-> (Pusher e Int, Citation -> Int)
-> (Peeker e Int, Citation -> Int -> Citation)
-> Member e (DocumentedFunction e) Citation
forall e b a fn.
LuaError e =>
Name
-> Text
-> (Pusher e b, a -> b)
-> (Peeker e b, a -> b -> a)
-> Member e fn a
property Name
"hash" Text
"hash number"
      (Pusher e Int
forall a e. (Integral a, Show a) => a -> LuaE e ()
pushIntegral, Citation -> Int
citationHash)
      (Peeker e Int
forall a e. (Integral a, Read a) => Peeker e a
peekIntegral, \Citation
citation Int
hash -> Citation
citation{ citationHash :: Int
citationHash = Int
hash })
  , DocumentedFunction e -> Member e (DocumentedFunction e) Citation
forall e a.
DocumentedFunction e -> Member e (DocumentedFunction e) a
method (DocumentedFunction e -> Member e (DocumentedFunction e) Citation)
-> DocumentedFunction e -> Member e (DocumentedFunction e) Citation
forall a b. (a -> b) -> a -> b
$ Name
-> (Citation -> LuaE e Citation)
-> HsFnPrecursor e (Citation -> LuaE e Citation)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"clone"
    ### return
    HsFnPrecursor e (Citation -> LuaE e Citation)
-> Parameter e Citation -> HsFnPrecursor e (LuaE e Citation)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> DocumentedType e Citation -> Text -> Text -> Parameter e Citation
forall e a itemtype.
LuaError e =>
DocumentedTypeWithList e a itemtype
-> Text -> Text -> Parameter e a
udparam DocumentedType e Citation
forall e. LuaError e => DocumentedType e Citation
typeCitation Text
"obj" Text
""
    HsFnPrecursor e (LuaE e Citation)
-> FunctionResults e Citation -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Citation -> Text -> Text -> FunctionResults e Citation
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Citation
forall e. LuaError e => Pusher e Citation
pushCitation Text
"Citation" Text
"copy of obj"
  ]
{-# INLINABLE typeCitation #-}

-- | Constructor function for 'Citation' elements.
mkCitation :: LuaError e => DocumentedFunction e
mkCitation :: DocumentedFunction e
mkCitation = Name
-> (Text
    -> CitationMode
    -> Maybe [Inline]
    -> Maybe [Inline]
    -> Maybe Int
    -> Maybe Int
    -> LuaE e Citation)
-> HsFnPrecursor
     e
     (Text
      -> CitationMode
      -> Maybe [Inline]
      -> Maybe [Inline]
      -> Maybe Int
      -> Maybe Int
      -> LuaE e Citation)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"Citation"
  ### (\cid mode mprefix msuffix mnote_num mhash ->
         cid `seq` mode `seq` mprefix `seq` msuffix `seq`
         mnote_num `seq` mhash `seq` return $! Citation
           { citationId = cid
           , citationMode = mode
           , citationPrefix = fromMaybe mempty mprefix
           , citationSuffix = fromMaybe mempty msuffix
           , citationNoteNum = fromMaybe 0 mnote_num
           , citationHash = fromMaybe 0 mhash
           })
  HsFnPrecursor
  e
  (Text
   -> CitationMode
   -> Maybe [Inline]
   -> Maybe [Inline]
   -> Maybe Int
   -> Maybe Int
   -> LuaE e Citation)
-> Parameter e Text
-> HsFnPrecursor
     e
     (CitationMode
      -> Maybe [Inline]
      -> Maybe [Inline]
      -> Maybe Int
      -> Maybe Int
      -> LuaE e Citation)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Text -> Text -> Text -> Text -> Parameter e Text
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e Text
forall e. Peeker e Text
peekText Text
"string" Text
"cid" Text
"citation ID (e.g. bibtex key)"
  HsFnPrecursor
  e
  (CitationMode
   -> Maybe [Inline]
   -> Maybe [Inline]
   -> Maybe Int
   -> Maybe Int
   -> LuaE e Citation)
-> Parameter e CitationMode
-> HsFnPrecursor
     e
     (Maybe [Inline]
      -> Maybe [Inline] -> Maybe Int -> Maybe Int -> LuaE e Citation)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e CitationMode
-> Text -> Text -> Text -> Parameter e CitationMode
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e CitationMode
forall e. Peeker e CitationMode
peekCitationMode Text
"CitationMode" Text
"mode" Text
"citation rendering mode"
  HsFnPrecursor
  e
  (Maybe [Inline]
   -> Maybe [Inline] -> Maybe Int -> Maybe Int -> LuaE e Citation)
-> Parameter e (Maybe [Inline])
-> HsFnPrecursor
     e (Maybe [Inline] -> Maybe Int -> Maybe Int -> LuaE e Citation)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e [Inline]
-> Text -> Text -> Text -> Parameter e (Maybe [Inline])
forall e a.
Peeker e a -> Text -> Text -> Text -> Parameter e (Maybe a)
optionalParameter Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy Text
"prefix" Text
"Inlines" Text
""
  HsFnPrecursor
  e (Maybe [Inline] -> Maybe Int -> Maybe Int -> LuaE e Citation)
-> Parameter e (Maybe [Inline])
-> HsFnPrecursor e (Maybe Int -> Maybe Int -> LuaE e Citation)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e [Inline]
-> Text -> Text -> Text -> Parameter e (Maybe [Inline])
forall e a.
Peeker e a -> Text -> Text -> Text -> Parameter e (Maybe a)
optionalParameter Peeker e [Inline]
forall e. LuaError e => Peeker e [Inline]
peekInlinesFuzzy Text
"suffix" Text
"Inlines" Text
""
  HsFnPrecursor e (Maybe Int -> Maybe Int -> LuaE e Citation)
-> Parameter e (Maybe Int)
-> HsFnPrecursor e (Maybe Int -> LuaE e Citation)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Int -> Text -> Text -> Text -> Parameter e (Maybe Int)
forall e a.
Peeker e a -> Text -> Text -> Text -> Parameter e (Maybe a)
optionalParameter Peeker e Int
forall a e. (Integral a, Read a) => Peeker e a
peekIntegral Text
"note_num" Text
"integer" Text
"note number"
  HsFnPrecursor e (Maybe Int -> LuaE e Citation)
-> Parameter e (Maybe Int) -> HsFnPrecursor e (LuaE e Citation)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Int -> Text -> Text -> Text -> Parameter e (Maybe Int)
forall e a.
Peeker e a -> Text -> Text -> Text -> Parameter e (Maybe a)
optionalParameter Peeker e Int
forall a e. (Integral a, Read a) => Peeker e a
peekIntegral Text
"hash" Text
"integer" Text
"hash number"
  HsFnPrecursor e (LuaE e Citation)
-> FunctionResults e Citation -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Citation -> Text -> Text -> FunctionResults e Citation
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Citation
forall e. LuaError e => Pusher e Citation
pushCitation Text
"Citation" Text
"new citation object"
  #? "Creates a single citation."