{-# LANGUAGE CPP #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE LambdaCase #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TypeApplications #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}
module HsLua.Module.DocLayout (
documentedModule
, pushModule
, preloadModule
, description
, fields
, functions
, after_break
, before_non_blank
, blankline
, blanklines
, braces
, brackets
, cblock
, chomp
, concat
, cr
, double_quotes
, empty
, flush
, hang
, inside
, lblock
, literal
, nest
, nestle
, nowrap
, parens
, prefixed
, quotes
, rblock
, space
, vfill
, render
, is_empty
, height
, min_offset
, offset
, real_length
, update_column
, peekDoc
, pushDoc
)
where
import Prelude hiding (concat)
import Data.List (intersperse)
import Data.Text (Text)
import HsLua as Lua hiding (concat)
import Text.DocLayout (Doc, (<+>), ($$), ($+$))
import qualified Data.Text as T
import qualified Text.DocLayout as Doc
#if ! MIN_VERSION_base(4, 11, 0)
import Data.Monoid ((<>))
#endif
description :: Text
description :: Text
description = Text
"Plain-text document layouting."
documentedModule :: LuaError e => Module e
documentedModule :: Module e
documentedModule = Module :: forall e.
Name
-> Text
-> [Field e]
-> [DocumentedFunction e]
-> [(Operation, DocumentedFunction e)]
-> Module e
Module
{ moduleName :: Name
moduleName = Name
"doclayout"
, moduleFields :: [Field e]
moduleFields = [Field e]
forall e. LuaError e => [Field e]
fields
, moduleDescription :: Text
moduleDescription = Text
description
, moduleFunctions :: [DocumentedFunction e]
moduleFunctions = [DocumentedFunction e]
forall e. LuaError e => [DocumentedFunction e]
functions
, moduleOperations :: [(Operation, DocumentedFunction e)]
moduleOperations = []
}
fields :: LuaError e => [Field e]
fields :: [Field e]
fields =
[ Field e
forall e. LuaError e => Field e
blankline
, Field e
forall e. LuaError e => Field e
cr
, Field e
forall e. LuaError e => Field e
empty
, Field e
forall e. LuaError e => Field e
space
]
blankline :: LuaError e => Field e
blankline :: Field e
blankline = Field :: forall e. Text -> Text -> LuaE e () -> Field e
Field
{ fieldName :: Text
fieldName = Text
"blankline"
, fieldDescription :: Text
fieldDescription = Text
"Inserts a blank line unless one exists already."
, fieldPushValue :: LuaE e ()
fieldPushValue = Pusher e (Doc Text)
forall e. LuaError e => Pusher e (Doc Text)
pushDoc Doc Text
forall a. Doc a
Doc.blankline
}
cr :: LuaError e => Field e
cr :: Field e
cr = Field :: forall e. Text -> Text -> LuaE e () -> Field e
Field
{ fieldName :: Text
fieldName = Text
"cr"
, fieldDescription :: Text
fieldDescription = Text
"A carriage return. Does nothing if we're at " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
Text
"the beginning of a line; " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
Text
"otherwise inserts a newline."
, fieldPushValue :: LuaE e ()
fieldPushValue = Pusher e (Doc Text)
forall e. LuaError e => Pusher e (Doc Text)
pushDoc Doc Text
forall a. Doc a
Doc.cr
}
empty :: LuaError e => Field e
empty :: Field e
empty = Field :: forall e. Text -> Text -> LuaE e () -> Field e
Field
{ fieldName :: Text
fieldName = Text
"empty"
, fieldDescription :: Text
fieldDescription = Text
"The empty document."
, fieldPushValue :: LuaE e ()
fieldPushValue = Pusher e (Doc Text)
forall e. LuaError e => Pusher e (Doc Text)
pushDoc Doc Text
forall a. Doc a
Doc.empty
}
space :: LuaError e => Field e
space :: Field e
space = Field :: forall e. Text -> Text -> LuaE e () -> Field e
Field
{ fieldName :: Text
fieldName = Text
"space"
, fieldDescription :: Text
fieldDescription = Text
"A breaking (reflowable) space."
, fieldPushValue :: LuaE e ()
fieldPushValue = Pusher e (Doc Text)
forall e. LuaError e => Pusher e (Doc Text)
pushDoc Doc Text
forall a. Doc a
Doc.space
}
functions :: LuaError e => [DocumentedFunction e]
functions :: [DocumentedFunction e]
functions =
[
DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
after_break
, DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
before_non_blank
, DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
blanklines
, DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
braces
, DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
brackets
, DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
cblock
, DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
chomp
, DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
concat
, DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
double_quotes
, DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
flush
, DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
hang
, DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
inside
, DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
lblock
, DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
literal
, DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
nest
, DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
nestle
, DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
nowrap
, DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
parens
, DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
prefixed
, DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
quotes
, DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
rblock
, DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
vfill
, DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
render
, DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
is_empty
, DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
height
, DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
min_offset
, DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
offset
, DocumentedFunction e
forall e. DocumentedFunction e
real_length
, DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
update_column
]
typeDoc :: LuaError e => DocumentedType e (Doc Text)
typeDoc :: DocumentedType e (Doc Text)
typeDoc = Name
-> [(Operation, DocumentedFunction e)]
-> [Member e (DocumentedFunction e) (Doc Text)]
-> DocumentedType e (Doc Text)
forall e a.
LuaError e =>
Name
-> [(Operation, DocumentedFunction e)]
-> [Member e (DocumentedFunction e) a]
-> DocumentedType e a
deftype Name
"Doc"
[ Operation
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
forall e.
Operation
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
operation Operation
Add (DocumentedFunction e -> (Operation, DocumentedFunction e))
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
forall a b. (a -> b) -> a -> b
$ (Doc Text -> Doc Text -> Doc Text) -> Text -> DocumentedFunction e
forall e.
LuaError e =>
(Doc Text -> Doc Text -> Doc Text) -> Text -> DocumentedFunction e
binaryOp Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
(<+>)
Text
"Concatenated docs, with breakable space between them."
, Operation
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
forall e.
Operation
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
operation Operation
Concat (DocumentedFunction e -> (Operation, DocumentedFunction e))
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
forall a b. (a -> b) -> a -> b
$ (Doc Text -> Doc Text -> Doc Text) -> Text -> DocumentedFunction e
forall e.
LuaError e =>
(Doc Text -> Doc Text -> Doc Text) -> Text -> DocumentedFunction e
binaryOp Doc Text -> Doc Text -> Doc Text
forall a. Semigroup a => a -> a -> a
(<>) Text
"Concatenation of the input docs"
, Operation
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
forall e.
Operation
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
operation Operation
Div (DocumentedFunction e -> (Operation, DocumentedFunction e))
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
forall a b. (a -> b) -> a -> b
$ (Doc Text -> Doc Text -> Doc Text) -> Text -> DocumentedFunction e
forall e.
LuaError e =>
(Doc Text -> Doc Text -> Doc Text) -> Text -> DocumentedFunction e
binaryOp Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
($$) Text
"Puts a above b"
, 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
$ (Doc Text -> Doc Text -> LuaE e Bool)
-> HsFnPrecursor e (Doc Text -> Doc Text -> LuaE e Bool)
forall a e. a -> HsFnPrecursor e a
lambda
### liftPure2 (==)
HsFnPrecursor e (Doc Text -> Doc Text -> LuaE e Bool)
-> Parameter e (Doc Text)
-> HsFnPrecursor e (Doc Text -> LuaE e Bool)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"a"
HsFnPrecursor e (Doc Text -> LuaE e Bool)
-> Parameter e (Doc Text) -> HsFnPrecursor e (LuaE e Bool)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"b"
HsFnPrecursor e (LuaE e Bool)
-> FunctionResults e Bool -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e Bool
forall e. Text -> FunctionResults e Bool
boolResult Text
"whether the two Docs are equal"
, Operation
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
forall e.
Operation
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
operation Operation
Idiv (DocumentedFunction e -> (Operation, DocumentedFunction e))
-> DocumentedFunction e -> (Operation, DocumentedFunction e)
forall a b. (a -> b) -> a -> b
$ (Doc Text -> Doc Text -> Doc Text) -> Text -> DocumentedFunction e
forall e.
LuaError e =>
(Doc Text -> Doc Text -> Doc Text) -> Text -> DocumentedFunction e
binaryOp Doc Text -> Doc Text -> Doc Text
forall a. Doc a -> Doc a -> Doc a
($+$) Text
"Puts a above b"
, 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
$ (Doc Text -> LuaE e Text)
-> HsFnPrecursor e (Doc Text -> LuaE e Text)
forall a e. a -> HsFnPrecursor e a
lambda
### liftPure (Doc.render Nothing)
HsFnPrecursor e (Doc Text -> LuaE e Text)
-> Parameter e (Doc Text) -> HsFnPrecursor e (LuaE e Text)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"doc"
HsFnPrecursor e (LuaE e Text)
-> FunctionResults e Text -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e Text
forall e. Text -> FunctionResults e Text
textResult Text
"Rendered Doc without reflowing."
]
[ DocumentedFunction e -> Member e (DocumentedFunction e) (Doc Text)
forall e a.
DocumentedFunction e -> Member e (DocumentedFunction e) a
method DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
before_non_blank
, DocumentedFunction e -> Member e (DocumentedFunction e) (Doc Text)
forall e a.
DocumentedFunction e -> Member e (DocumentedFunction e) a
method DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
braces
, DocumentedFunction e -> Member e (DocumentedFunction e) (Doc Text)
forall e a.
DocumentedFunction e -> Member e (DocumentedFunction e) a
method DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
brackets
, DocumentedFunction e -> Member e (DocumentedFunction e) (Doc Text)
forall e a.
DocumentedFunction e -> Member e (DocumentedFunction e) a
method DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
chomp
, DocumentedFunction e -> Member e (DocumentedFunction e) (Doc Text)
forall e a.
DocumentedFunction e -> Member e (DocumentedFunction e) a
method DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
double_quotes
, DocumentedFunction e -> Member e (DocumentedFunction e) (Doc Text)
forall e a.
DocumentedFunction e -> Member e (DocumentedFunction e) a
method DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
is_empty
, DocumentedFunction e -> Member e (DocumentedFunction e) (Doc Text)
forall e a.
DocumentedFunction e -> Member e (DocumentedFunction e) a
method DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
flush
, DocumentedFunction e -> Member e (DocumentedFunction e) (Doc Text)
forall e a.
DocumentedFunction e -> Member e (DocumentedFunction e) a
method DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
height
, DocumentedFunction e -> Member e (DocumentedFunction e) (Doc Text)
forall e a.
DocumentedFunction e -> Member e (DocumentedFunction e) a
method DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
min_offset
, DocumentedFunction e -> Member e (DocumentedFunction e) (Doc Text)
forall e a.
DocumentedFunction e -> Member e (DocumentedFunction e) a
method DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
nestle
, DocumentedFunction e -> Member e (DocumentedFunction e) (Doc Text)
forall e a.
DocumentedFunction e -> Member e (DocumentedFunction e) a
method DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
nowrap
, DocumentedFunction e -> Member e (DocumentedFunction e) (Doc Text)
forall e a.
DocumentedFunction e -> Member e (DocumentedFunction e) a
method DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
offset
, DocumentedFunction e -> Member e (DocumentedFunction e) (Doc Text)
forall e a.
DocumentedFunction e -> Member e (DocumentedFunction e) a
method DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
parens
, DocumentedFunction e -> Member e (DocumentedFunction e) (Doc Text)
forall e a.
DocumentedFunction e -> Member e (DocumentedFunction e) a
method DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
quotes
, DocumentedFunction e -> Member e (DocumentedFunction e) (Doc Text)
forall e a.
DocumentedFunction e -> Member e (DocumentedFunction e) a
method DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
update_column
, DocumentedFunction e -> Member e (DocumentedFunction e) (Doc Text)
forall e a.
DocumentedFunction e -> Member e (DocumentedFunction e) a
method DocumentedFunction e
forall e. LuaError e => DocumentedFunction e
vfill
]
where
binaryOp :: (Doc Text -> Doc Text -> Doc Text) -> Text -> DocumentedFunction e
binaryOp Doc Text -> Doc Text -> Doc Text
op Text
descr = (Doc Text -> Doc Text -> LuaE e (Doc Text))
-> HsFnPrecursor e (Doc Text -> Doc Text -> LuaE e (Doc Text))
forall a e. a -> HsFnPrecursor e a
lambda
### liftPure2 op
HsFnPrecursor e (Doc Text -> Doc Text -> LuaE e (Doc Text))
-> Parameter e (Doc Text)
-> HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"a"
HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
-> Parameter e (Doc Text) -> HsFnPrecursor e (LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"b"
HsFnPrecursor e (LuaE e (Doc Text))
-> FunctionResults e (Doc Text) -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e (Doc Text)
forall e. LuaError e => Text -> FunctionResults e (Doc Text)
docResult Text
descr
render :: LuaError e => DocumentedFunction e
render :: DocumentedFunction e
render = Name
-> (Doc Text -> Maybe Int -> LuaE e Text)
-> HsFnPrecursor e (Doc Text -> Maybe Int -> LuaE e Text)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"render"
### liftPure2 (flip Doc.render)
HsFnPrecursor e (Doc Text -> Maybe Int -> LuaE e Text)
-> Parameter e (Doc Text)
-> HsFnPrecursor e (Maybe Int -> LuaE e Text)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"doc"
HsFnPrecursor e (Maybe Int -> LuaE e Text)
-> Parameter e (Maybe Int) -> HsFnPrecursor e (LuaE e Text)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Parameter e Int -> Parameter e (Maybe Int)
forall e a. Parameter e a -> Parameter e (Maybe a)
opt (Text -> Text -> Parameter e Int
forall a e. (Read a, Integral a) => Text -> Text -> Parameter e a
integralParam Text
"colwidth" Text
"")
HsFnPrecursor e (LuaE e Text)
-> FunctionResults e Text -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Pusher e Text -> Text -> Text -> FunctionResults e Text
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e Text
forall e. Pusher e Text
pushText Text
"Doc" Text
"rendered doc"
#? ("Render a @'Doc'@. The text is reflowed on breakable spaces" <>
"to match the given line length. Text is not reflowed if the" <>
"line length parameter is omitted or nil.")
is_empty :: LuaError e => DocumentedFunction e
is_empty :: DocumentedFunction e
is_empty = Name
-> (Doc Text -> LuaE e Bool)
-> HsFnPrecursor e (Doc Text -> LuaE e Bool)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"is_empty"
### liftPure Doc.isEmpty
HsFnPrecursor e (Doc Text -> LuaE e Bool)
-> Parameter e (Doc Text) -> HsFnPrecursor e (LuaE e Bool)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"doc"
HsFnPrecursor e (LuaE e Bool)
-> FunctionResults e Bool -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e Bool
forall e. Text -> FunctionResults e Bool
boolResult Text
"`true` iff `doc` is the empty document, `false` otherwise."
#? "Checks whether a doc is empty."
offset :: LuaError e => DocumentedFunction e
offset :: DocumentedFunction e
offset = Name
-> (Doc Text -> LuaE e Int)
-> HsFnPrecursor e (Doc Text -> LuaE e Int)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"offset"
### liftPure Doc.offset
HsFnPrecursor e (Doc Text -> LuaE e Int)
-> Parameter e (Doc Text) -> HsFnPrecursor e (LuaE e Int)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"doc"
HsFnPrecursor e (LuaE e Int)
-> FunctionResults e Int -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e Int
forall a e. (Integral a, Show a) => Text -> FunctionResults e a
integralResult Text
"doc width"
#? "Returns the width of a `Doc` as number of characters."
min_offset :: LuaError e => DocumentedFunction e
min_offset :: DocumentedFunction e
min_offset = Name
-> (Doc Text -> LuaE e Int)
-> HsFnPrecursor e (Doc Text -> LuaE e Int)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"min_offset"
### liftPure Doc.minOffset
HsFnPrecursor e (Doc Text -> LuaE e Int)
-> Parameter e (Doc Text) -> HsFnPrecursor e (LuaE e Int)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"doc"
HsFnPrecursor e (LuaE e Int)
-> FunctionResults e Int -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e Int
forall a e. (Integral a, Show a) => Text -> FunctionResults e a
integralResult Text
"minimal possible width"
#? ("Returns the minimal width of a `Doc` when reflowed at " <>
"breakable spaces.")
update_column :: LuaError e => DocumentedFunction e
update_column :: DocumentedFunction e
update_column = Name
-> (Doc Text -> Int -> LuaE e Int)
-> HsFnPrecursor e (Doc Text -> Int -> LuaE e Int)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"update_column"
### liftPure2 Doc.updateColumn
HsFnPrecursor e (Doc Text -> Int -> LuaE e Int)
-> Parameter e (Doc Text) -> HsFnPrecursor e (Int -> LuaE e Int)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"doc"
HsFnPrecursor e (Int -> LuaE e Int)
-> Parameter e Int -> HsFnPrecursor e (LuaE e Int)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Text -> Parameter e Int
forall a e. (Read a, Integral a) => Text -> Text -> Parameter e a
integralParam Text
"i" Text
""
HsFnPrecursor e (LuaE e Int)
-> FunctionResults e Int -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e Int
forall a e. (Integral a, Show a) => Text -> FunctionResults e a
integralResult Text
"column number"
#? ("Returns the column that would be occupied by the last " <>
"laid out character.")
height :: LuaError e => DocumentedFunction e
height :: DocumentedFunction e
height = Name
-> (Doc Text -> LuaE e Int)
-> HsFnPrecursor e (Doc Text -> LuaE e Int)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"height"
### liftPure Doc.height
HsFnPrecursor e (Doc Text -> LuaE e Int)
-> Parameter e (Doc Text) -> HsFnPrecursor e (LuaE e Int)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"doc"
HsFnPrecursor e (LuaE e Int)
-> FunctionResults e Int -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e Int
forall a e. (Integral a, Show a) => Text -> FunctionResults e a
integralResult Text
"doc height"
#? "Returns the height of a block or other Doc."
real_length :: DocumentedFunction e
real_length :: DocumentedFunction e
real_length = Name
-> (Text -> LuaE e Int) -> HsFnPrecursor e (Text -> LuaE e Int)
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"real_length"
### liftPure Doc.realLength
HsFnPrecursor e (Text -> LuaE e Int)
-> Parameter e Text -> HsFnPrecursor e (LuaE e Int)
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Text -> Parameter e Text
forall e. Text -> Text -> Parameter e Text
textParam Text
"str" Text
""
HsFnPrecursor e (LuaE e Int)
-> FunctionResults e Int -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e Int
forall a e. (Integral a, Show a) => Text -> FunctionResults e a
integralResult Text
"text length"
#? ("Returns the real length of a string in a monospace font: " <>
"0 for a combining chaeracter, 1 for a regular character, " <>
"2 for an East Asian wide character.")
after_break :: LuaError e => DocumentedFunction e
after_break :: DocumentedFunction e
after_break = Name
-> (Text -> LuaE e (Doc Text))
-> HsFnPrecursor e (Text -> LuaE e (Doc Text))
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"after_break"
### liftPure Doc.afterBreak
HsFnPrecursor e (Text -> LuaE e (Doc Text))
-> Parameter e Text -> HsFnPrecursor e (LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Text -> Parameter e Text
forall e. Text -> Text -> Parameter e Text
textParam Text
"text" Text
""
HsFnPrecursor e (LuaE e (Doc Text))
-> FunctionResults e (Doc Text) -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e (Doc Text)
forall e. LuaError e => Text -> FunctionResults e (Doc Text)
docResult Text
"new doc"
#? ("Creates a `Doc` which is conditionally included only if it" <>
"comes at the beginning of a line.")
before_non_blank :: LuaError e => DocumentedFunction e
before_non_blank :: DocumentedFunction e
before_non_blank = Name
-> (Doc Text -> LuaE e (Doc Text))
-> HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"before_non_blank"
### liftPure Doc.beforeNonBlank
HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
-> Parameter e (Doc Text) -> HsFnPrecursor e (LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"doc"
HsFnPrecursor e (LuaE e (Doc Text))
-> FunctionResults e (Doc Text) -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e (Doc Text)
forall e. LuaError e => Text -> FunctionResults e (Doc Text)
docResult Text
"conditional doc"
#? ("Conditionally includes the given `doc` unless it is " <>
"followed by a blank space.")
blanklines :: LuaError e => DocumentedFunction e
blanklines :: DocumentedFunction e
blanklines = Name
-> (Int -> LuaE e (Doc Text))
-> HsFnPrecursor e (Int -> LuaE e (Doc Text))
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"blanklines"
### liftPure Doc.blanklines
HsFnPrecursor e (Int -> LuaE e (Doc Text))
-> Parameter e Int -> HsFnPrecursor e (LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Text -> Parameter e Int
forall a e. (Read a, Integral a) => Text -> Text -> Parameter e a
integralParam Text
"n" Text
""
HsFnPrecursor e (LuaE e (Doc Text))
-> FunctionResults e (Doc Text) -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e (Doc Text)
forall e. LuaError e => Text -> FunctionResults e (Doc Text)
docResult Text
"conditional blank lines"
#? "Inserts blank lines unless they exist already."
braces :: LuaError e => DocumentedFunction e
braces :: DocumentedFunction e
braces = Name
-> (Doc Text -> LuaE e (Doc Text))
-> HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"braces"
### liftPure Doc.braces
HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
-> Parameter e (Doc Text) -> HsFnPrecursor e (LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"doc"
HsFnPrecursor e (LuaE e (Doc Text))
-> FunctionResults e (Doc Text) -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e (Doc Text)
forall e. LuaError e => Text -> FunctionResults e (Doc Text)
docResult Text
"doc enclosed by {}."
#? "Puts the `doc` in curly braces."
brackets :: LuaError e => DocumentedFunction e
brackets :: DocumentedFunction e
brackets = Name
-> (Doc Text -> LuaE e (Doc Text))
-> HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"brackets"
### liftPure Doc.brackets
HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
-> Parameter e (Doc Text) -> HsFnPrecursor e (LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"doc"
HsFnPrecursor e (LuaE e (Doc Text))
-> FunctionResults e (Doc Text) -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e (Doc Text)
forall e. LuaError e => Text -> FunctionResults e (Doc Text)
docResult Text
"doc enclosed by []."
#? "Puts the `doc` in square brackets"
cblock :: LuaError e => DocumentedFunction e
cblock :: DocumentedFunction e
cblock = Name
-> (Int -> Doc Text -> LuaE e (Doc Text))
-> HsFnPrecursor e (Int -> Doc Text -> LuaE e (Doc Text))
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"cblock"
### liftPure2 Doc.cblock
HsFnPrecursor e (Int -> Doc Text -> LuaE e (Doc Text))
-> Parameter e Int
-> HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Int -> Text -> Text -> Text -> Parameter e Int
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e Int
forall a e. (Integral a, Read a) => Peeker e a
peekIntegral Text
"integer" Text
"width" Text
"block width in chars"
HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
-> Parameter e (Doc Text) -> HsFnPrecursor e (LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"doc"
HsFnPrecursor e (LuaE e (Doc Text))
-> FunctionResults e (Doc Text) -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e (Doc Text)
forall e. LuaError e => Text -> FunctionResults e (Doc Text)
docResult (Text
"doc, aligned centered in a block with max" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
Text
"`width` chars per line.")
#? ("Creates a block with the given width and content, " <>
"aligned centered.")
chomp :: LuaError e => DocumentedFunction e
chomp :: DocumentedFunction e
chomp = Name
-> (Doc Text -> LuaE e (Doc Text))
-> HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"chomp"
### liftPure Doc.chomp
HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
-> Parameter e (Doc Text) -> HsFnPrecursor e (LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"doc"
HsFnPrecursor e (LuaE e (Doc Text))
-> FunctionResults e (Doc Text) -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e (Doc Text)
forall e. LuaError e => Text -> FunctionResults e (Doc Text)
docResult Text
"`doc` without trailing blanks"
#? "Chomps trailing blank space off of the `doc`."
concat :: LuaError e => DocumentedFunction e
concat :: DocumentedFunction e
concat = Name
-> ([Doc Text] -> Maybe (Doc Text) -> LuaE e (Doc Text))
-> HsFnPrecursor
e ([Doc Text] -> Maybe (Doc Text) -> LuaE e (Doc Text))
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"concat"
### liftPure2 (\docs optSep -> mconcat $
maybe docs (`intersperse` docs) optSep)
HsFnPrecursor
e ([Doc Text] -> Maybe (Doc Text) -> LuaE e (Doc Text))
-> Parameter e [Doc Text]
-> HsFnPrecursor e (Maybe (Doc Text) -> LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e [Doc Text]
-> Text -> Text -> Text -> Parameter e [Doc Text]
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter (Peeker e (Doc Text) -> Peeker e [Doc Text]
forall a e. LuaError e => Peeker e a -> Peeker e [a]
peekList Peeker e (Doc Text)
forall e. LuaError e => Peeker e (Doc Text)
peekDoc) Text
"`{Doc,...}`" Text
"docs" Text
"list of Docs"
HsFnPrecursor e (Maybe (Doc Text) -> LuaE e (Doc Text))
-> Parameter e (Maybe (Doc Text))
-> HsFnPrecursor e (LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Parameter e (Doc Text) -> Parameter e (Maybe (Doc Text))
forall e a. Parameter e a -> Parameter e (Maybe a)
opt (Peeker e (Doc Text)
-> Text -> Text -> Text -> Parameter e (Doc Text)
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e (Doc Text)
forall e. LuaError e => Peeker e (Doc Text)
peekDoc Text
"Doc" Text
"sep" Text
"separator")
HsFnPrecursor e (LuaE e (Doc Text))
-> FunctionResults e (Doc Text) -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e (Doc Text)
forall e. LuaError e => Text -> FunctionResults e (Doc Text)
docResult Text
"concatenated doc"
#? "Concatenates a list of `Doc`s."
double_quotes :: LuaError e => DocumentedFunction e
double_quotes :: DocumentedFunction e
double_quotes = Name
-> (Doc Text -> LuaE e (Doc Text))
-> HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"double_quotes"
### liftPure Doc.doubleQuotes
HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
-> Parameter e (Doc Text) -> HsFnPrecursor e (LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"doc"
HsFnPrecursor e (LuaE e (Doc Text))
-> FunctionResults e (Doc Text) -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e (Doc Text)
forall e. LuaError e => Text -> FunctionResults e (Doc Text)
docResult Text
"`doc` enclosed by `\"` chars"
#? "Wraps a `Doc` in double quotes."
flush :: LuaError e => DocumentedFunction e
flush :: DocumentedFunction e
flush = Name
-> (Doc Text -> LuaE e (Doc Text))
-> HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"flush"
### liftPure Doc.flush
HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
-> Parameter e (Doc Text) -> HsFnPrecursor e (LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"doc"
HsFnPrecursor e (LuaE e (Doc Text))
-> FunctionResults e (Doc Text) -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e (Doc Text)
forall e. LuaError e => Text -> FunctionResults e (Doc Text)
docResult Text
"flushed `doc`"
#? "Makes a `Doc` flush against the left margin."
hang :: LuaError e => DocumentedFunction e
hang :: DocumentedFunction e
hang = Name
-> (Int -> Doc Text -> Doc Text -> LuaE e (Doc Text))
-> HsFnPrecursor
e (Int -> Doc Text -> Doc Text -> LuaE e (Doc Text))
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"hang"
### liftPure3 Doc.hang
HsFnPrecursor e (Int -> Doc Text -> Doc Text -> LuaE e (Doc Text))
-> Parameter e Int
-> HsFnPrecursor e (Doc Text -> Doc Text -> LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Int -> Text -> Text -> Text -> Parameter e Int
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e Int
forall a e. (Integral a, Read a) => Peeker e a
peekIntegral Text
"integer" Text
"ind" Text
"indentation width"
HsFnPrecursor e (Doc Text -> Doc Text -> LuaE e (Doc Text))
-> Parameter e (Doc Text)
-> HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"start"
HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
-> Parameter e (Doc Text) -> HsFnPrecursor e (LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"doc"
HsFnPrecursor e (LuaE e (Doc Text))
-> FunctionResults e (Doc Text) -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e (Doc Text)
forall e. LuaError e => Text -> FunctionResults e (Doc Text)
docResult (Text
"`doc` prefixed by `start` on the first line, " Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
Text
"subsequent lines indented by `ind` spaces.")
#? "Creates a hanging indent."
inside :: LuaError e => DocumentedFunction e
inside :: DocumentedFunction e
inside = Name
-> (Doc Text -> Doc Text -> Doc Text -> LuaE e (Doc Text))
-> HsFnPrecursor
e (Doc Text -> Doc Text -> Doc Text -> LuaE e (Doc Text))
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"inside"
### liftPure3 Doc.inside
HsFnPrecursor
e (Doc Text -> Doc Text -> Doc Text -> LuaE e (Doc Text))
-> Parameter e (Doc Text)
-> HsFnPrecursor e (Doc Text -> Doc Text -> LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"start"
HsFnPrecursor e (Doc Text -> Doc Text -> LuaE e (Doc Text))
-> Parameter e (Doc Text)
-> HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"end"
HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
-> Parameter e (Doc Text) -> HsFnPrecursor e (LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"contents"
HsFnPrecursor e (LuaE e (Doc Text))
-> FunctionResults e (Doc Text) -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e (Doc Text)
forall e. LuaError e => Text -> FunctionResults e (Doc Text)
docResult Text
"enclosed contents"
#? "Encloses a `Doc` inside a start and end `Doc`."
lblock :: LuaError e => DocumentedFunction e
lblock :: DocumentedFunction e
lblock = Name
-> (Int -> Doc Text -> LuaE e (Doc Text))
-> HsFnPrecursor e (Int -> Doc Text -> LuaE e (Doc Text))
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"lblock"
### liftPure2 Doc.lblock
HsFnPrecursor e (Int -> Doc Text -> LuaE e (Doc Text))
-> Parameter e Int
-> HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Int -> Text -> Text -> Text -> Parameter e Int
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e Int
forall a e. (Integral a, Read a) => Peeker e a
peekIntegral Text
"integer" Text
"width" Text
"block width in chars"
HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
-> Parameter e (Doc Text) -> HsFnPrecursor e (LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"doc"
HsFnPrecursor e (LuaE e (Doc Text))
-> FunctionResults e (Doc Text) -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e (Doc Text)
forall e. LuaError e => Text -> FunctionResults e (Doc Text)
docResult Text
"doc put into block with max `width` chars per line."
#? ("Creates a block with the given width and content, " <>
"aligned to the left.")
literal :: LuaError e => DocumentedFunction e
literal :: DocumentedFunction e
literal = Name
-> (Text -> LuaE e (Doc Text))
-> HsFnPrecursor e (Text -> LuaE e (Doc Text))
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"literal"
### liftPure Doc.literal
HsFnPrecursor e (Text -> LuaE e (Doc Text))
-> Parameter e Text -> HsFnPrecursor e (LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Text -> Parameter e Text
forall e. Text -> Text -> Parameter e Text
textParam Text
"string" Text
""
HsFnPrecursor e (LuaE e (Doc Text))
-> FunctionResults e (Doc Text) -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e (Doc Text)
forall e. LuaError e => Text -> FunctionResults e (Doc Text)
docResult Text
"doc contatining just the literal string"
#? "Creates a `Doc` from a string."
nest :: LuaError e => DocumentedFunction e
nest :: DocumentedFunction e
nest = Name
-> (Int -> Doc Text -> LuaE e (Doc Text))
-> HsFnPrecursor e (Int -> Doc Text -> LuaE e (Doc Text))
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"nest"
### liftPure2 Doc.nest
HsFnPrecursor e (Int -> Doc Text -> LuaE e (Doc Text))
-> Parameter e Int
-> HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Int -> Text -> Text -> Text -> Parameter e Int
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e Int
forall a e. (Integral a, Read a) => Peeker e a
peekIntegral Text
"integer" Text
"ind" Text
"indentation size"
HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
-> Parameter e (Doc Text) -> HsFnPrecursor e (LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"doc"
HsFnPrecursor e (LuaE e (Doc Text))
-> FunctionResults e (Doc Text) -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e (Doc Text)
forall e. LuaError e => Text -> FunctionResults e (Doc Text)
docResult Text
"`doc` indented by `ind` spaces"
#? "Indents a `Doc` by the specified number of spaces."
nestle :: LuaError e => DocumentedFunction e
nestle :: DocumentedFunction e
nestle = Name
-> (Doc Text -> LuaE e (Doc Text))
-> HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"nestle"
### liftPure Doc.nestle
HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
-> Parameter e (Doc Text) -> HsFnPrecursor e (LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"doc"
HsFnPrecursor e (LuaE e (Doc Text))
-> FunctionResults e (Doc Text) -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e (Doc Text)
forall e. LuaError e => Text -> FunctionResults e (Doc Text)
docResult Text
"`doc` with leading blanks removed"
#? "Removes leading blank lines from a `Doc`."
nowrap :: LuaError e => DocumentedFunction e
nowrap :: DocumentedFunction e
nowrap = Name
-> (Doc Text -> LuaE e (Doc Text))
-> HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"nowrap"
### liftPure Doc.nowrap
HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
-> Parameter e (Doc Text) -> HsFnPrecursor e (LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"doc"
HsFnPrecursor e (LuaE e (Doc Text))
-> FunctionResults e (Doc Text) -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e (Doc Text)
forall e. LuaError e => Text -> FunctionResults e (Doc Text)
docResult Text
"same as input, but non-reflowable"
#? "Makes a `Doc` non-reflowable."
parens :: LuaError e => DocumentedFunction e
parens :: DocumentedFunction e
parens = Name
-> (Doc Text -> LuaE e (Doc Text))
-> HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"parens"
### liftPure Doc.parens
HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
-> Parameter e (Doc Text) -> HsFnPrecursor e (LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"doc"
HsFnPrecursor e (LuaE e (Doc Text))
-> FunctionResults e (Doc Text) -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e (Doc Text)
forall e. LuaError e => Text -> FunctionResults e (Doc Text)
docResult Text
"doc enclosed by ()."
#? "Puts the `doc` in parentheses."
prefixed :: LuaError e => DocumentedFunction e
prefixed :: DocumentedFunction e
prefixed = Name
-> (String -> Doc Text -> LuaE e (Doc Text))
-> HsFnPrecursor e (String -> Doc Text -> LuaE e (Doc Text))
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"prefixed"
### liftPure2 Doc.prefixed
HsFnPrecursor e (String -> Doc Text -> LuaE e (Doc Text))
-> Parameter e String
-> HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e String -> Text -> Text -> Text -> Parameter e String
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e String
forall e. Peeker e String
peekString Text
"string" Text
"prefix" Text
"prefix for each line"
HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
-> Parameter e (Doc Text) -> HsFnPrecursor e (LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"doc"
HsFnPrecursor e (LuaE e (Doc Text))
-> FunctionResults e (Doc Text) -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e (Doc Text)
forall e. LuaError e => Text -> FunctionResults e (Doc Text)
docResult Text
"prefixed `doc`"
#? ("Uses the specified string as a prefix for every line of " <>
"the inside document (except the first, if not at the " <>
"beginning of the line).")
quotes :: LuaError e => DocumentedFunction e
quotes :: DocumentedFunction e
quotes = Name
-> (Doc Text -> LuaE e (Doc Text))
-> HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"quotes"
### liftPure Doc.quotes
HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
-> Parameter e (Doc Text) -> HsFnPrecursor e (LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"doc"
HsFnPrecursor e (LuaE e (Doc Text))
-> FunctionResults e (Doc Text) -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e (Doc Text)
forall e. LuaError e => Text -> FunctionResults e (Doc Text)
docResult Text
"doc enclosed in `'`."
#? "Wraps a `Doc` in single quotes."
rblock :: LuaError e => DocumentedFunction e
rblock :: DocumentedFunction e
rblock = Name
-> (Int -> Doc Text -> LuaE e (Doc Text))
-> HsFnPrecursor e (Int -> Doc Text -> LuaE e (Doc Text))
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"rblock"
### liftPure2 Doc.rblock
HsFnPrecursor e (Int -> Doc Text -> LuaE e (Doc Text))
-> Parameter e Int
-> HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Peeker e Int -> Text -> Text -> Text -> Parameter e Int
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e Int
forall a e. (Integral a, Read a) => Peeker e a
peekIntegral Text
"integer" Text
"width" Text
"block width in chars"
HsFnPrecursor e (Doc Text -> LuaE e (Doc Text))
-> Parameter e (Doc Text) -> HsFnPrecursor e (LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Parameter e (Doc Text)
forall e. LuaError e => Text -> Parameter e (Doc Text)
docParam Text
"doc"
HsFnPrecursor e (LuaE e (Doc Text))
-> FunctionResults e (Doc Text) -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e (Doc Text)
forall e. LuaError e => Text -> FunctionResults e (Doc Text)
docResult (Text
"doc, right aligned in a block with max" Text -> Text -> Text
forall a. Semigroup a => a -> a -> a
<>
Text
"`width` chars per line.")
#? ("Creates a block with the given width and content, " <>
"aligned to the right.")
vfill :: LuaError e => DocumentedFunction e
vfill :: DocumentedFunction e
vfill = Name
-> (Text -> LuaE e (Doc Text))
-> HsFnPrecursor e (Text -> LuaE e (Doc Text))
forall a e. Name -> a -> HsFnPrecursor e a
defun Name
"vfill"
### liftPure Doc.vfill
HsFnPrecursor e (Text -> LuaE e (Doc Text))
-> Parameter e Text -> HsFnPrecursor e (LuaE e (Doc Text))
forall e a b.
HsFnPrecursor e (a -> b) -> Parameter e a -> HsFnPrecursor e b
<#> Text -> Text -> Parameter e Text
forall e. Text -> Text -> Parameter e Text
textParam Text
"border" Text
""
HsFnPrecursor e (LuaE e (Doc Text))
-> FunctionResults e (Doc Text) -> DocumentedFunction e
forall e a.
HsFnPrecursor e (LuaE e a)
-> FunctionResults e a -> DocumentedFunction e
=#> Text -> FunctionResults e (Doc Text)
forall e. LuaError e => Text -> FunctionResults e (Doc Text)
docResult Text
"automatically expanding border Doc"
#? ("An expandable border that, when placed next to a box, " <>
"expands to the height of the box. Strings cycle through the " <>
"list provided.")
peekDoc :: LuaError e => Peeker e (Doc Text)
peekDoc :: Peeker e (Doc Text)
peekDoc StackIndex
idx = LuaE e Type -> Peek e Type
forall e a. LuaE e a -> Peek e a
liftLua (StackIndex -> LuaE e Type
forall e. StackIndex -> LuaE e Type
Lua.ltype StackIndex
idx) Peek e Type -> (Type -> Peek e (Doc Text)) -> Peek e (Doc Text)
forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \case
Type
Lua.TypeString -> let stringToDoc :: Text -> Doc Text
stringToDoc Text
s = if Text -> Bool
T.null Text
s
then Doc Text
forall a. Doc a
Doc.empty
else Text -> Doc Text
forall a. HasChars a => a -> Doc a
Doc.literal Text
s
in Text -> Doc Text
stringToDoc (Text -> Doc Text) -> Peek e Text -> Peek e (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Peeker e Text
forall e. Peeker e Text
Lua.peekText StackIndex
idx
Type
Lua.TypeNumber -> Text -> Doc Text
forall a. HasChars a => a -> Doc a
Doc.literal (Text -> Doc Text) -> Peek e Text -> Peek e (Doc Text)
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Peeker e Text
forall e. Peeker e Text
Lua.peekText StackIndex
idx
Type
_ -> UDTypeWithList e (DocumentedFunction e) (Doc Text) Void
-> Peeker e (Doc Text)
forall e fn a itemtype.
LuaError e =>
UDTypeWithList e fn a itemtype -> Peeker e a
peekUD UDTypeWithList e (DocumentedFunction e) (Doc Text) Void
forall e. LuaError e => DocumentedType e (Doc Text)
typeDoc StackIndex
idx
pushDoc :: LuaError e => Pusher e (Doc Text)
pushDoc :: Pusher e (Doc Text)
pushDoc = UDTypeWithList e (DocumentedFunction e) (Doc Text) Void
-> Pusher e (Doc Text)
forall e fn a itemtype.
LuaError e =>
UDTypeWithList e fn a itemtype -> a -> LuaE e ()
pushUD UDTypeWithList e (DocumentedFunction e) (Doc Text) Void
forall e. LuaError e => DocumentedType e (Doc Text)
typeDoc
instance Peekable (Doc Text) where
safepeek :: Peeker e (Doc Text)
safepeek = Peeker e (Doc Text)
forall e. LuaError e => Peeker e (Doc Text)
peekDoc
instance Pushable (Doc Text) where
push :: Doc Text -> LuaE e ()
push = Doc Text -> LuaE e ()
forall e. LuaError e => Pusher e (Doc Text)
pushDoc
docParam :: LuaError e => Text -> Parameter e (Doc Text)
docParam :: Text -> Parameter e (Doc Text)
docParam Text
name = Peeker e (Doc Text)
-> Text -> Text -> Text -> Parameter e (Doc Text)
forall e a. Peeker e a -> Text -> Text -> Text -> Parameter e a
parameter Peeker e (Doc Text)
forall e. LuaError e => Peeker e (Doc Text)
peekDoc Text
"Doc" Text
name Text
""
docResult :: LuaError e
=> Text
-> FunctionResults e (Doc Text)
docResult :: Text -> FunctionResults e (Doc Text)
docResult = Pusher e (Doc Text) -> Text -> Text -> FunctionResults e (Doc Text)
forall e a. Pusher e a -> Text -> Text -> FunctionResults e a
functionResult Pusher e (Doc Text)
forall e. LuaError e => Pusher e (Doc Text)
pushDoc Text
"Doc"