Add type annotations to assist ghci.

This commit is contained in:
John MacFarlane 2020-01-04 09:55:15 -08:00
parent c5b6321b21
commit 8ed749702f
4 changed files with 13 additions and 7 deletions

View file

@ -1,6 +1,7 @@
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE LambdaCase #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
{- |
@ -67,7 +68,8 @@ instance Pushable ReaderOptions where
indexReaderOptions _tbl (AnyValue key) = do
Lua.ltype key >>= \case
Lua.TypeString -> Lua.peek key >>= \case
"defaultImageExtension" -> Lua.push defaultImageExtension
("defaultImageExtension" :: Text.Text)
-> Lua.push defaultImageExtension
"indentedCodeClasses" -> Lua.push indentedCodeClasses
"stripComments" -> Lua.push stripComments
"tabStop" -> Lua.push tabStop

View file

@ -1,6 +1,7 @@
{-# OPTIONS_GHC -fno-warn-orphans #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Lua.Marshaling.Version
Copyright : © 2019 Albert Krewinkel
@ -19,6 +20,7 @@ module Text.Pandoc.Lua.Marshaling.Version
where
import Prelude
import Data.Text (Text)
import Data.Maybe (fromMaybe)
import Data.Version (Version (..), makeVersion, parseVersion, showVersion)
import Foreign.Lua (Lua, Optional (..), NumResults,
@ -103,7 +105,7 @@ __index v (AnyValue k) = do
Lua.push (Lua.Optional versionPart)
return 1
Lua.TypeString -> do
str <- Lua.peek k
(str :: Text) <- Lua.peek k
if str == "must_be_at_least"
then 1 <$ Lua.pushHaskellFunction must_be_at_least
else 1 <$ Lua.pushnil

View file

@ -1,4 +1,5 @@
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Lua.Module.MediaBag
Copyright : Copyright © 2017-2019 Albert Krewinkel
@ -108,9 +109,9 @@ mediaDirectoryFn = do
addEntry :: Lua.Integer -> (FilePath, MimeType, Int) -> Lua ()
addEntry idx (fp, mimeType, contentLength) = do
Lua.newtable
Lua.push "path" *> Lua.push fp *> Lua.rawset (-3)
Lua.push "type" *> Lua.push mimeType *> Lua.rawset (-3)
Lua.push "length" *> Lua.push contentLength *> Lua.rawset (-3)
Lua.push ("path" :: T.Text) *> Lua.push fp *> Lua.rawset (-3)
Lua.push ("type" :: T.Text) *> Lua.push mimeType *> Lua.rawset (-3)
Lua.push ("length" :: T.Text) *> Lua.push contentLength *> Lua.rawset (-3)
Lua.rawseti (-2) idx
fetch :: T.Text

View file

@ -1,6 +1,7 @@
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE NoImplicitPrelude #-}
{-# LANGUAGE OverloadedStrings #-}
{- |
Module : Text.Pandoc.Lua.Util
Copyright : © 20122019 John MacFarlane,
@ -31,9 +32,9 @@ import Control.Monad (unless, when)
import Foreign.Lua ( Lua, NumArgs, NumResults, Peekable, Pushable, StackIndex
, Status, ToHaskellFunction )
import Text.Pandoc.Class (readDataFile, runIOorExplode, setUserDataDir)
import qualified Foreign.Lua as Lua
import qualified Text.Pandoc.UTF8 as UTF8
import Data.Text (Text)
-- | Get value behind key from table at given index.
rawField :: Peekable a => StackIndex -> String -> Lua a
@ -104,7 +105,7 @@ getTag :: StackIndex -> Lua String
getTag idx = do
-- push metatable or just the table
Lua.getmetatable idx >>= \hasMT -> unless hasMT (Lua.pushvalue idx)
Lua.push "tag"
Lua.push ("tag" :: Text)
Lua.rawget (Lua.nthFromTop 2)
Lua.tostring Lua.stackTop <* Lua.pop 2 >>= \case
Nothing -> Lua.throwException "untagged value"