Pretty.hs 5.2 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144
  1. {-# LANGUAGE RecordWildCards #-}
  2. {-# LANGUAGE OverloadedStrings #-}
  3. {-# LANGUAGE ScopedTypeVariables #-}
  4. module Data.SCargot.Pretty
  5. ( -- * Pretty-Printing
  6. prettyPrintSExpr
  7. -- * Pretty-Printing Control
  8. , LayoutOptions(..)
  9. , Indent(..)
  10. -- * Default Printing Strategies
  11. , basicPrint
  12. , flatPrint
  13. ) where
  14. import Data.Monoid ((<>))
  15. import Data.Text (Text)
  16. import qualified Data.Text as T
  17. import Data.SCargot.Repr
  18. -- | The 'Indent' type is used to determine how to indent subsequent
  19. -- s-expressions in a list, after printing the head of the list.
  20. data Indent
  21. = Swing -- ^ A 'Swing' indent will indent subsequent exprs some fixed
  22. -- amount more than the current line.
  23. --
  24. -- > (foo
  25. -- > bar
  26. -- > baz
  27. -- > quux)
  28. | SwingAfter Int -- ^ A 'SwingAfter' @n@ indent will try to print the
  29. -- first @n@ expressions after the head on the same
  30. -- line as the head, and all after will be swung.
  31. -- 'SwingAfter' @0@ is equivalent to 'Swing'.
  32. --
  33. -- > (foo bar
  34. -- > baz
  35. -- > quux)
  36. | Align -- ^ An 'Align' indent will print the first expression after
  37. -- the head on the same line, and subsequent expressions will
  38. -- be aligned with that one.
  39. --
  40. -- > (foo bar
  41. -- > baz
  42. -- > quux)
  43. deriving (Eq, Show)
  44. -- | A 'LayoutOptions' value describes the strategy taken in
  45. -- pretty-printing a 'SExpr'.
  46. data LayoutOptions a = LayoutOptions
  47. { atomPrinter :: a -> Text
  48. -- ^ How to serialize a given atom to 'Text'.
  49. , swingIndent :: SExpr a -> Indent
  50. -- ^ How to indent subsequent expressions, as determined by
  51. -- the head of the list.
  52. , indentAmount :: Int
  53. -- ^ How much to indent after a swung indentation.
  54. , maxWidth :: Maybe Int
  55. -- ^ The maximum width (if any) If this is 'None' then
  56. -- the resulting s-expression will always be printed
  57. -- on a single line.
  58. }
  59. -- | A default 'LayoutOptions' struct that will always print a 'SExpr'
  60. -- as a single line.
  61. flatPrint :: (a -> Text) -> LayoutOptions a
  62. flatPrint printer = LayoutOptions
  63. { atomPrinter = printer
  64. , swingIndent = const Swing
  65. , indentAmount = 2
  66. , maxWidth = Nothing
  67. }
  68. -- | A default 'LayoutOptions' struct that will always swing subsequent
  69. -- expressions onto later lines if they're too long, indenting them
  70. -- by two spaces.
  71. basicPrint :: (a -> Text) -> LayoutOptions a
  72. basicPrint printer = LayoutOptions
  73. { atomPrinter = printer
  74. , swingIndent = const Swing
  75. , indentAmount = 2
  76. , maxWidth = Just 80
  77. }
  78. -- Sort of like 'unlines' but without the trailing newline
  79. joinLines :: [Text] -> Text
  80. joinLines = T.intercalate "\n"
  81. -- Indents a line by n spaces
  82. indent :: Int -> Text -> Text
  83. indent n ts = T.replicate n " " <> ts
  84. -- Indents every line n spaces, and adds a newline to the beginning
  85. -- used in swung indents
  86. indentAll :: Int -> [Text] -> Text
  87. indentAll n = ("\n" <>) . joinLines . map (indent n)
  88. -- Indents every line but the first by some amount
  89. -- used in aligned indents
  90. indentSubsequent :: Int -> [Text] -> Text
  91. indentSubsequent _ [] = ""
  92. indentSubsequent _ [t] = t
  93. indentSubsequent n (t:ts) = joinLines (t : go ts)
  94. where go = map (indent n)
  95. -- oh god this code is so disgusting
  96. -- i'm sorry to everyone i let down by writing this
  97. -- i swear i'll do better in the future i promise i have to
  98. -- for my sake and for everyone's
  99. -- | Pretty-print a 'SExpr' according to the options in a
  100. -- 'LayoutOptions' value.
  101. prettyPrintSExpr :: LayoutOptions a -> SExpr a -> Text
  102. prettyPrintSExpr LayoutOptions { .. } = pHead 0
  103. where pHead _ SNil = "()"
  104. pHead _ (SAtom a) = atomPrinter a
  105. pHead ind (SCons x xs) = gather ind x xs id
  106. gather _ _ (SAtom _) _ = error "no dotted pretty printing yet!"
  107. gather ind h (SCons x xs) k = gather ind h xs (k . (x:))
  108. gather ind h SNil k = "(" <> hd <> body <> ")"
  109. where hd = indentSubsequent ind [pHead (ind+1) h]
  110. lst = k []
  111. flat = T.unwords (map (pHead (ind+1)) lst)
  112. headWidth = T.length hd + 1
  113. indented =
  114. case swingIndent h of
  115. SwingAfter n ->
  116. let (l, ls) = splitAt n lst
  117. t = T.unwords (map (pHead (ind+1)) l)
  118. ts = indentAll (ind + indentAmount)
  119. (map (pHead (ind + indentAmount)) ls)
  120. in t <> ts
  121. Swing ->
  122. indentAll (ind + indentAmount)
  123. (map (pHead (ind + indentAmount)) lst)
  124. Align ->
  125. indentSubsequent (ind + headWidth + 1)
  126. (map (pHead (ind + headWidth + 1)) lst)
  127. body
  128. | length lst == 0 = ""
  129. | Just maxAmt <- maxWidth
  130. , T.length flat + ind > maxAmt = " " <> indented
  131. | otherwise = " " <> flat