Copyright | (c) Karl Cronburg 2018 |
---|---|
License | BSD3 |
Maintainer | karl@cs.tufts.edu |
Stability | experimental |
Portability | POSIX |
Safe Haskell | Safe |
Language | Haskell2010 |
I want to have something like Show whereby every time I add a new type to the system, I can implement a function that gets called by existing code which happens to have types that get parametrized by that type. I don't want to modify an existing file / centralizing all of the types in my system into a single file makes little sense because then that one file becomes a hub / single point of failure.
- I need a typeclass (no modifying existing files, but they need to call my new code without passing around a new show function)
- The prettify function of that typeclass needs to return a state monad so that recursive calls keep the state
- A pshow function needs to evalState on the prettify function with an initial indentation of zero (along with any other future state values...)
Synopsis
- data PState = PState {}
- type PrettyM val = State PState val
- type Pretty = PrettyM ()
- class Prettify t where
- prettify :: t -> Pretty
- prettifyList :: [t] -> Pretty
- initPState :: PState
- pLine :: Text -> Pretty
- pStr' :: String -> Pretty
- pStr :: Text -> Pretty
- pChr :: Char -> Pretty
- _doIf :: Monad m => m () -> Bool -> m ()
- _pIndent :: Pretty
- _pNewLine :: Pretty
- pshow :: Prettify t => t -> Text
- pshow' :: Prettify t => t -> String
- pshowList :: Prettify t => [t] -> Text
- pshowList' :: Prettify t => [t] -> String
- pshowIndent :: Prettify t => Int -> t -> Text
- rshow :: Show t => t -> Pretty
- pParens :: StateT PState Identity a -> StateT PState Identity ()
- incrIndent :: Int -> Pretty
- setIndent :: Int -> Pretty
- pCount :: Prettify v => v -> PrettyM Int
- pListLines :: Prettify v => [v] -> Pretty
- prettifyList_ :: Prettify t => [t] -> Pretty
- sepBy :: Monad m => m a -> [m ()] -> m ()
- _sepBy :: Monad m => m a1 -> m a2 -> m b -> m b
Documentation
Pretty-printing state
PState | |
|
type Pretty = PrettyM () Source #
No value being threaded through the monad (because result is in str
)
class Prettify t where Source #
Define the Prettify
type class for your pretty-printable type t
.
prettify :: t -> Pretty Source #
Defines how to pretty-print some type.
prettify :: Show t => t -> Pretty Source #
Defines how to pretty-print some type.
prettifyList :: [t] -> Pretty Source #
Lists are pretty-printed specially.
Instances
initPState :: PState Source #
Initial Pretty state with safe soft and hard column defaults.
pLine :: Text -> Pretty Source #
Prettify a string by putting it on the end of the current string state
pStr :: Text -> Pretty Source #
This currently assumes all input strings contain no newlines, and that this is
only called on relatively small strings because strings running over the end
of the hard column limit get dumped onto the next line no matter what.
T.Texts can run over the soft limit, but hitting the soft limit after a call
to pStr
forces a newline.
_doIf :: Monad m => m () -> Bool -> m () Source #
Gets rid of if-then-else lines in the Pretty monad code:
pshowList' :: Prettify t => [t] -> String Source #
pshowIndent :: Prettify t => Int -> t -> Text Source #
Run the pretty-printer with a specific indentation level.
pParens :: StateT PState Identity a -> StateT PState Identity () Source #
Parenthesize something in Pretty
.
incrIndent :: Int -> Pretty Source #
Increment the indentation level by modifying the pretty-printer state.
setIndent :: Int -> Pretty Source #
Like incrIndent
but set indentation level instead of incrementing.
pCount :: Prettify v => v -> PrettyM Int Source #
Prettify the given value and compute the number of characters consumed as a result.
pListLines :: Prettify v => [v] -> Pretty Source #
Pretty-print a list with one entry per line.
prettifyList_ :: Prettify t => [t] -> Pretty Source #
Prettify a list with possibly more than one entry per line.