Improved Haddocks for pretty-printing
Getty Ritter
10 years ago
| 3 | 3 | {-# LANGUAGE ScopedTypeVariables #-} |
| 4 | 4 | |
| 5 | 5 | module Data.SCargot.Pretty |
| 6 |
( |
|
| 6 | ( -- * Pretty-Printing | |
| 7 | prettyPrintSExpr | |
| 8 | -- * Pretty-Printing Control | |
| 9 | , LayoutOptions(..) | |
| 7 | 10 | , Indent(..) |
| 11 | -- * Default Printing Strategies | |
| 8 | 12 | , basicPrint |
| 9 | 13 | , flatPrint |
| 10 | , prettyPrintSExpr | |
| 11 | 14 | ) where |
| 12 | 15 | |
| 13 | 16 | import Data.Monoid ((<>)) |
| 16 | 19 | |
| 17 | 20 | import Data.SCargot.Repr |
| 18 | 21 | |
| 22 | -- | The 'Indent' type is used to determine how to indent subsequent | |
| 23 | -- s-expressions in a list, after printing the head of the list. | |
| 19 | 24 | data Indent |
| 20 | = Swing | |
| 21 | | SwingAfter Int | |
| 22 |
|
|
| 25 | = Swing -- ^ A 'Swing' indent will indent subsequent exprs some fixed | |
| 26 | -- amount more than the current line. | |
| 27 | -- | |
| 28 | -- > (foo | |
| 29 | -- > bar | |
| 30 | -- > baz | |
| 31 | -- > quux) | |
| 32 | | SwingAfter Int -- ^ A 'SwingAfter' @n@ indent will try to print the | |
| 33 | -- first @n@ expressions after the head on the same | |
| 34 | -- line as the head, and all after will be swung. | |
| 35 | -- 'SwingAfter' @0@ is equivalent to 'Swing'. | |
| 36 | -- | |
| 37 | -- > (foo bar | |
| 38 | -- > baz | |
| 39 | -- > quux) | |
| 40 | | Align -- ^ An 'Align' indent will print the first expression after | |
| 41 | -- the head on the same line, and subsequent expressions will | |
| 42 | -- be aligned with that one. | |
| 43 | -- | |
| 44 | -- > (foo bar | |
| 45 | -- > baz | |
| 46 | -- > quux) | |
| 23 | 47 | deriving (Eq, Show) |
| 24 | 48 | |
| 25 | -- | A 'LayoutOptions' value describes how to pretty-print a 'SExpr'. | |
| 26 | -- It describes how to print atoms, what horizontal space to fit | |
| 27 | -- it into, and other related options. | |
| 28 | -- | |
| 29 | -- The 'swingIndent' value might require a big of explanation: in | |
| 30 | -- pretty-printing s-expressions, you have the option of whether | |
| 31 | -- to 'swing' expressions which get pushed to subsequent lines | |
| 32 | -- to the left, or to align them along the right. e.g. the | |
| 33 | -- s-expression @(foo a b)@ could use a non-swing indent as | |
| 34 | -- | |
| 35 | -- > (foo arg-one | |
| 36 | -- > arg-two) | |
| 37 | -- | |
| 38 | -- or a swing indent as | |
| 39 | -- | |
| 40 | -- > (foo arg-one | |
| 41 | -- > arg-two) | |
| 42 | -- | |
| 43 | -- often, in formatting Lisp code, control structures will | |
| 44 | -- swing subsequent expressions, as in | |
| 45 | -- | |
| 46 | -- > (define (factorial n) | |
| 47 | -- > (if (= n 0) | |
| 48 | -- > 1 | |
| 49 | -- > (* n (fact (- n 1))))) | |
| 50 | -- | |
| 51 | -- but most functions will _not_ swing: | |
| 52 | -- | |
| 53 | -- > (call-my-func arg-number-one | |
| 54 | -- > arg-number-two | |
| 55 | -- > arg-number-three) | |
| 56 | -- | |
| 57 | -- The 'swingIndent' field lets you choose whether or not to | |
| 58 | -- swing subsequent s-expressions based on the atom in the car | |
| 59 | -- position of a list. You can default to always swinging subsequent | |
| 60 | -- expressions with @const True@ and never with @const False@, or | |
| 61 | -- choose based on some more advanced criteria. _If_ a swing happens, | |
| 62 | -- subsequent lines are indented based on the 'indentAmount' variable; | |
| 63 | -- otherwise, subsequent lines are indented based on the size of the | |
| 64 | -- @car@ of the list. | |
| 49 | -- | A 'LayoutOptions' value describes the strategy taken in | |
| 50 | -- pretty-printing a 'SExpr'. | |
| 65 | 51 | data LayoutOptions a = LayoutOptions |
| 66 | { atomPrinter :: a -> Text -- ^ How to serialize a given atom to 'Text'. | |
| 67 | , swingIndent :: SExpr a -> Indent -- ^ Whether or not to swing | |
| 68 | , indentAmount :: Int -- ^ How much to indent after a swing | |
| 69 | , maxWidth :: Maybe Int -- ^ The maximum width (if any) | |
| 52 | { atomPrinter :: a -> Text | |
| 53 | -- ^ How to serialize a given atom to 'Text'. | |
| 54 | , swingIndent :: SExpr a -> Indent | |
| 55 | -- ^ How to indent subsequent expressions, as determined by | |
| 56 | -- the head of the list. | |
| 57 | , indentAmount :: Int | |
| 58 | -- ^ How much to indent after a swung indentation. | |
| 59 | , maxWidth :: Maybe Int | |
| 60 | -- ^ The maximum width (if any) If this is 'None' then | |
| 61 | -- the resulting s-expression will always be printed | |
| 62 | -- on a single line. | |
| 70 | 63 | } |
| 71 | 64 | |
| 65 | -- | A default 'LayoutOptions' struct that will always print a 'SExpr' | |
| 66 | -- as a single line. | |
| 72 | 67 | flatPrint :: (a -> Text) -> LayoutOptions a |
| 73 | 68 | flatPrint printer = LayoutOptions |
| 74 | 69 | { atomPrinter = printer |
| 77 | 72 | , maxWidth = Nothing |
| 78 | 73 | } |
| 79 | 74 | |
| 75 | -- | A default 'LayoutOptions' struct that will always swing subsequent | |
| 76 | -- expressions onto later lines if they're too long, indenting them | |
| 77 | -- by two spaces. | |
| 80 | 78 | basicPrint :: (a -> Text) -> LayoutOptions a |
| 81 | 79 | basicPrint printer = LayoutOptions |
| 82 | 80 | { atomPrinter = printer |
| 108 | 106 | -- i'm sorry to everyone i let down by writing this |
| 109 | 107 | -- i swear i'll do better in the future i promise i have to |
| 110 | 108 | -- for my sake and for everyone's |
| 109 | ||
| 110 | -- | Pretty-print a 'Sexpr' according to the options in a | |
| 111 | -- 'LayoutOptions' value. | |
| 111 | 112 | prettyPrintSExpr :: LayoutOptions a -> SExpr a -> Text |
| 112 | 113 | prettyPrintSExpr LayoutOptions { .. } = pHead 0 |
| 113 | 114 | where pHead _ SNil = "()" |