{-# LANGUAGE DeriveDataTypeable   #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE UndecidableInstances #-}
{- |
Module      : Text.Pandoc.Lua.Marshaling.List
Copyright   : © 2012-2020 John MacFarlane
              © 2017-2020 Albert Krewinkel
License     : GNU GPL, version 2 or above
Maintainer  : Albert Krewinkel <tarleb+pandoc@moltkeplatz.de>
Stability   : alpha

Marshaling/unmarshaling instances for @pandoc.List@s.
-}
module Text.Pandoc.Lua.Marshaling.List
  ( List (..)
  ) where

import Data.Data (Data)
import Foreign.Lua (Peekable, Pushable)
import Text.Pandoc.Walk (Walkable (..))
import Text.Pandoc.Lua.Util (defineHowTo, pushViaConstructor)

import qualified Foreign.Lua as Lua

-- | List wrapper which is marshalled as @pandoc.List@.
newtype List a = List { List a -> [a]
fromList :: [a] }
  deriving (Typeable (List a)
DataType
Constr
Typeable (List a)
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> List a -> c (List a))
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c (List a))
-> (List a -> Constr)
-> (List a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c (List a)))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (List a)))
-> ((forall b. Data b => b -> b) -> List a -> List a)
-> (forall r r'.
    (r -> r' -> r)
    -> r -> (forall d. Data d => d -> r') -> List a -> r)
-> (forall r r'.
    (r' -> r -> r)
    -> r -> (forall d. Data d => d -> r') -> List a -> r)
-> (forall u. (forall d. Data d => d -> u) -> List a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> List a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> List a -> m (List a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> List a -> m (List a))
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> List a -> m (List a))
-> Data (List a)
List a -> DataType
List a -> Constr
(forall d. Data d => c (t d)) -> Maybe (c (List a))
(forall b. Data b => b -> b) -> List a -> List a
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> List a -> c (List a)
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (List a)
forall a. Data a => Typeable (List a)
forall a. Data a => List a -> DataType
forall a. Data a => List a -> Constr
forall a.
Data a =>
(forall b. Data b => b -> b) -> List a -> List a
forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> List a -> u
forall a u. Data a => (forall d. Data d => d -> u) -> List a -> [u]
forall a r r'.
Data a =>
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> List a -> r
forall a r r'.
Data a =>
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> List a -> r
forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> List a -> m (List a)
forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> List a -> m (List a)
forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (List a)
forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> List a -> c (List a)
forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (List a))
forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (List a))
forall a.
Typeable a
-> (forall (c :: * -> *).
    (forall d b. Data d => c (d -> b) -> d -> c b)
    -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> List a -> u
forall u. (forall d. Data d => d -> u) -> List a -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> List a -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> List a -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> List a -> m (List a)
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> List a -> m (List a)
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (List a)
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> List a -> c (List a)
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c (List a))
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (List a))
$cList :: Constr
$tList :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> List a -> m (List a)
$cgmapMo :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> List a -> m (List a)
gmapMp :: (forall d. Data d => d -> m d) -> List a -> m (List a)
$cgmapMp :: forall a (m :: * -> *).
(Data a, MonadPlus m) =>
(forall d. Data d => d -> m d) -> List a -> m (List a)
gmapM :: (forall d. Data d => d -> m d) -> List a -> m (List a)
$cgmapM :: forall a (m :: * -> *).
(Data a, Monad m) =>
(forall d. Data d => d -> m d) -> List a -> m (List a)
gmapQi :: Int -> (forall d. Data d => d -> u) -> List a -> u
$cgmapQi :: forall a u.
Data a =>
Int -> (forall d. Data d => d -> u) -> List a -> u
gmapQ :: (forall d. Data d => d -> u) -> List a -> [u]
$cgmapQ :: forall a u. Data a => (forall d. Data d => d -> u) -> List a -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> List a -> r
$cgmapQr :: forall a r r'.
Data a =>
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> List a -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> List a -> r
$cgmapQl :: forall a r r'.
Data a =>
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> List a -> r
gmapT :: (forall b. Data b => b -> b) -> List a -> List a
$cgmapT :: forall a.
Data a =>
(forall b. Data b => b -> b) -> List a -> List a
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (List a))
$cdataCast2 :: forall a (t :: * -> * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (List a))
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c (List a))
$cdataCast1 :: forall a (t :: * -> *) (c :: * -> *).
(Data a, Typeable t) =>
(forall d. Data d => c (t d)) -> Maybe (c (List a))
dataTypeOf :: List a -> DataType
$cdataTypeOf :: forall a. Data a => List a -> DataType
toConstr :: List a -> Constr
$ctoConstr :: forall a. Data a => List a -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (List a)
$cgunfold :: forall a (c :: * -> *).
Data a =>
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c (List a)
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> List a -> c (List a)
$cgfoldl :: forall a (c :: * -> *).
Data a =>
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> List a -> c (List a)
$cp1Data :: forall a. Data a => Typeable (List a)
Data, List a -> List a -> Bool
(List a -> List a -> Bool)
-> (List a -> List a -> Bool) -> Eq (List a)
forall a. Eq a => List a -> List a -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: List a -> List a -> Bool
$c/= :: forall a. Eq a => List a -> List a -> Bool
== :: List a -> List a -> Bool
$c== :: forall a. Eq a => List a -> List a -> Bool
Eq, Int -> List a -> ShowS
[List a] -> ShowS
List a -> String
(Int -> List a -> ShowS)
-> (List a -> String) -> ([List a] -> ShowS) -> Show (List a)
forall a. Show a => Int -> List a -> ShowS
forall a. Show a => [List a] -> ShowS
forall a. Show a => List a -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [List a] -> ShowS
$cshowList :: forall a. Show a => [List a] -> ShowS
show :: List a -> String
$cshow :: forall a. Show a => List a -> String
showsPrec :: Int -> List a -> ShowS
$cshowsPrec :: forall a. Show a => Int -> List a -> ShowS
Show)

instance Pushable a => Pushable (List a) where
  push :: List a -> Lua ()
push (List [a]
xs) =
    String -> [a] -> Lua ()
forall a. PushViaCall a => String -> a
pushViaConstructor String
"List" [a]
xs

instance Peekable a => Peekable (List a) where
  peek :: StackIndex -> Lua (List a)
peek StackIndex
idx = String -> Lua (List a) -> Lua (List a)
forall a. String -> Lua a -> Lua a
defineHowTo String
"get List" (Lua (List a) -> Lua (List a)) -> Lua (List a) -> Lua (List a)
forall a b. (a -> b) -> a -> b
$ do
    [a]
xs <- StackIndex -> Lua [a]
forall a. Peekable a => StackIndex -> Lua a
Lua.peek StackIndex
idx
    List a -> Lua (List a)
forall (m :: * -> *) a. Monad m => a -> m a
return (List a -> Lua (List a)) -> List a -> Lua (List a)
forall a b. (a -> b) -> a -> b
$ [a] -> List a
forall a. [a] -> List a
List [a]
xs

-- List is just a wrapper, so we can reuse the walk instance for
-- unwrapped Hasekll lists.
instance Walkable [a] b => Walkable (List a) b where
  walkM :: (List a -> m (List a)) -> b -> m b
walkM List a -> m (List a)
f = ([a] -> m [a]) -> b -> m b
forall a b (m :: * -> *).
(Walkable a b, Monad m, Applicative m, Functor m) =>
(a -> m a) -> b -> m b
walkM ((List a -> [a]) -> m (List a) -> m [a]
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap List a -> [a]
forall a. List a -> [a]
fromList (m (List a) -> m [a]) -> ([a] -> m (List a)) -> [a] -> m [a]
forall b c a. (b -> c) -> (a -> b) -> a -> c
. List a -> m (List a)
f (List a -> m (List a)) -> ([a] -> List a) -> [a] -> m (List a)
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> List a
forall a. [a] -> List a
List)
  query :: (List a -> c) -> b -> c
query List a -> c
f = ([a] -> c) -> b -> c
forall a b c. (Walkable a b, Monoid c) => (a -> c) -> b -> c
query (List a -> c
f (List a -> c) -> ([a] -> List a) -> [a] -> c
forall b c a. (b -> c) -> (a -> b) -> a -> c
. [a] -> List a
forall a. [a] -> List a
List)