Safe Haskell | None |
---|---|
Language | Haskell2010 |
- encodeOne :: SExprPrinter atom carrier -> carrier -> Text
- encode :: SExprPrinter atom carrier -> [carrier] -> Text
- data SExprPrinter atom carrier
- data Indent
- = Swing
- | SwingAfter Int
- | Align
- setFromCarrier :: (c -> b) -> SExprPrinter a b -> SExprPrinter a c
- setMaxWidth :: Int -> SExprPrinter atom carrier -> SExprPrinter atom carrier
- removeMaxWidth :: SExprPrinter atom carrier -> SExprPrinter atom carrier
- setIndentAmount :: Int -> SExprPrinter atom carrier -> SExprPrinter atom carrier
- setIndentStrategy :: (SExpr atom -> Indent) -> SExprPrinter atom carrier -> SExprPrinter atom carrier
- basicPrint :: (atom -> Text) -> SExprPrinter atom (SExpr atom)
- flatPrint :: (atom -> Text) -> SExprPrinter atom (SExpr atom)
- unconstrainedPrint :: (atom -> Text) -> SExprPrinter atom (SExpr atom)
Pretty-Printing
encodeOne :: SExprPrinter atom carrier -> carrier -> Text Source #
Turn a single s-expression into a string according to a given
SExprPrinter
.
encode :: SExprPrinter atom carrier -> [carrier] -> Text Source #
Turn a list of s-expressions into a single string according to
a given SExprPrinter
.
Pretty-Printing Control
data SExprPrinter atom carrier Source #
A SExprPrinter
value describes how to print a given value as an
s-expression. The carrier
type parameter indicates the value
that will be printed, and the atom
parameter indicates the type
that will represent tokens in an s-expression structure.
The Indent
type is used to determine how to indent subsequent
s-expressions in a list, after printing the head of the list.
Swing | A (foo bar baz quux) |
SwingAfter Int | A (foo bar baz quux) |
Align | An (foo bar baz quux) |
setFromCarrier :: (c -> b) -> SExprPrinter a b -> SExprPrinter a c Source #
Modify the carrier type of a SExprPrinter
by describing how
to convert the new type back to the previous type. For example,
to pretty-print a well-formed s-expression, we can modify the
SExprPrinter
value as follows:
>>>
let printer = setFromCarrier fromWellFormed (basicPrint id)
>>>
encodeOne printer (WFSList [WFSAtom "ele", WFSAtom "phant"])
"(ele phant)"
setMaxWidth :: Int -> SExprPrinter atom carrier -> SExprPrinter atom carrier Source #
Dictate a maximum width for pretty-printed s-expressions.
>>>
let printer = setMaxWidth 8 (basicPrint id)
>>>
encodeOne printer (L [A "one", A "two", A "three"])
"(one \n two\n three)"
removeMaxWidth :: SExprPrinter atom carrier -> SExprPrinter atom carrier Source #
Allow the serialized s-expression to be arbitrarily wide. This makes all pretty-printing happen on a single line.
>>>
let printer = removeMaxWidth (basicPrint id)
>>>
encodeOne printer (L [A "one", A "two", A "three"])
"(one two three)"
setIndentAmount :: Int -> SExprPrinter atom carrier -> SExprPrinter atom carrier Source #
Set the number of spaces that a subsequent line will be indented after a swing indentation.
>>>
let printer = setMaxWidth 12 (basicPrint id)
>>>
encodeOne printer (L [A "elephant", A "pachyderm"])
"(elephant \n pachyderm)">>>
encodeOne (setIndentAmount 4) (L [A "elephant", A "pachyderm"])
"(elephant \n pachyderm)"
setIndentStrategy :: (SExpr atom -> Indent) -> SExprPrinter atom carrier -> SExprPrinter atom carrier Source #
Dictate how to indent subsequent lines based on the leading
subexpression in an s-expression. For details on how this works,
consult the documentation of the Indent
type.
>>>
let indent (A "def") = SwingAfter 1; indent _ = Swing
>>>
let printer = setIndentStrategy indent (setMaxWidth 8 (basicPrint id))
>>>
encodeOne printer (L [ A "def", L [ A "func", A "arg" ], A "body" ])
"(def (func arg)\n body)">>>
encodeOne printer (L [ A "elephant", A "among", A "pachyderms" ])
"(elephant \n among\n pachyderms)"
Default Printing Strategies
basicPrint :: (atom -> Text) -> SExprPrinter atom (SExpr atom) Source #
A default SExprPrinter
struct that will always swing subsequent
expressions onto later lines if they're too long, indenting them
by two spaces, and uses a soft maximum width of 80 characters
flatPrint :: (atom -> Text) -> SExprPrinter atom (SExpr atom) Source #
A default SExprPrinter
struct that will always print a SExpr
as a single line.
unconstrainedPrint :: (atom -> Text) -> SExprPrinter atom (SExpr atom) Source #
A default SExprPrinter
struct that will always swing subsequent
expressions onto later lines if they're too long, indenting them by
two spaces, but makes no effort to keep the pretty-printed sources
inside a maximum width. In the case that we want indented printing
but don't care about a "maximum" width, we can print more
efficiently than in other situations.