antlr-haskell-0.1.0.0: A Haskell implementation of the ANTLR top-down parser generator

Copyright(c) Karl Cronburg 2018
LicenseBSD3
Maintainerkarl@cs.tufts.edu
Stabilityexperimental
PortabilityPOSIX
Safe HaskellSafe
LanguageHaskell2010

Text.ANTLR.Pretty

Description

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

Documentation

data PState Source #

Pretty-printing state

Constructors

PState 

Fields

type PrettyM val = State PState val Source #

The pretty state monad

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.

Minimal complete definition

prettify

Methods

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
Prettify Bool Source # 
Instance details

Defined in Text.ANTLR.Pretty

Prettify Char Source # 
Instance details

Defined in Text.ANTLR.Pretty

Prettify Double Source # 
Instance details

Defined in Text.ANTLR.Pretty

Prettify Int Source # 
Instance details

Defined in Text.ANTLR.Pretty

Prettify () Source # 
Instance details

Defined in Text.ANTLR.Pretty

Methods

prettify :: () -> Pretty Source #

prettifyList :: [()] -> Pretty Source #

Prettify v => Prettify [v] Source # 
Instance details

Defined in Text.ANTLR.Pretty

Methods

prettify :: [v] -> Pretty Source #

prettifyList :: [[v]] -> Pretty Source #

Prettify v => Prettify (Maybe v) Source # 
Instance details

Defined in Text.ANTLR.Pretty

(Prettify a, Hashable a, Eq a) => Prettify (HashSet a) Source # 
Instance details

Defined in Text.ANTLR.Set

Prettify (Mutator s) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Prettify (Predicate s) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Prettify (StateFncn s) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Prettify ts => Prettify (Icon ts) Source # 
Instance details

Defined in Text.ANTLR.Parser

(Prettify a, Hashable a, Eq a) => Prettify (Stacks a) Source # 
Instance details

Defined in Text.ANTLR.Allstar.Stacks

Prettify nt => Prettify (ATNState nt) Source #

LaTeX style ATN states. TODO: check length of NT printed and put curly braces around it if more than one character.

Instance details

Defined in Text.ANTLR.Allstar.ATN

Prettify nts => Prettify (Prime nts) Source # 
Instance details

Defined in Text.ANTLR.LL1

Prettify nts => Prettify (ItemLHS nts) Source # 
Instance details

Defined in Text.ANTLR.LR

(Prettify a, Prettify b) => Prettify (a, b) Source # 
Instance details

Defined in Text.ANTLR.Pretty

Methods

prettify :: (a, b) -> Pretty Source #

prettifyList :: [(a, b)] -> Pretty Source #

(Prettify k, Prettify v) => Prettify (Map k v) Source # 
Instance details

Defined in Text.ANTLR.Pretty

Methods

prettify :: Map k v -> Pretty Source #

prettifyList :: [Map k v] -> Pretty Source #

(Prettify k, Prettify v, Hashable v, Eq v) => Prettify (Map k v) Source # 
Instance details

Defined in Text.ANTLR.MultiMap

Methods

prettify :: Map k v -> Pretty Source #

prettifyList :: [Map k v] -> Pretty Source #

(Prettify n, Prettify v) => Prettify (Token n v) Source # 
Instance details

Defined in Text.ANTLR.Lex.Tokenizer

(Prettify nts, Prettify ts) => Prettify (ProdElem nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

prettify :: ProdElem nts ts -> Pretty Source #

prettifyList :: [ProdElem nts ts] -> Pretty Source #

(Prettify nts, Prettify t) => Prettify (AST nts t) Source # 
Instance details

Defined in Text.ANTLR.Parser

Methods

prettify :: AST nts t -> Pretty Source #

prettifyList :: [AST nts t] -> Pretty Source #

(Prettify a, Prettify b, Prettify c) => Prettify (a, b, c) Source # 
Instance details

Defined in Text.ANTLR.Pretty

Methods

prettify :: (a, b, c) -> Pretty Source #

prettifyList :: [(a, b, c)] -> Pretty Source #

(Prettify s, Prettify nts, Prettify ts, Hashable ts, Eq ts, Hashable nts, Eq nts, Ord ts, Ord nts) => Prettify (Grammar s nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

prettify :: Grammar s nts ts -> Pretty Source #

prettifyList :: [Grammar s nts ts] -> Pretty Source #

(Prettify s, Prettify nts, Prettify ts) => Prettify (Production s nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

prettify :: Production s nts ts -> Pretty Source #

prettifyList :: [Production s nts ts] -> Pretty Source #

(Prettify s, Prettify nts, Prettify ts) => Prettify (ProdRHS s nts ts) Source # 
Instance details

Defined in Text.ANTLR.Grammar

Methods

prettify :: ProdRHS s nts ts -> Pretty Source #

prettifyList :: [ProdRHS s nts ts] -> Pretty Source #

(Prettify ast, Prettify nts, Prettify (StripEOF (Sym t)), Prettify t) => Prettify (ParseEvent ast nts t) Source # 
Instance details

Defined in Text.ANTLR.Parser

Methods

prettify :: ParseEvent ast nts t -> Pretty Source #

prettifyList :: [ParseEvent ast nts t] -> Pretty Source #

(Prettify s, Prettify nt, Prettify t) => Prettify (Edge s nt t) Source # 
Instance details

Defined in Text.ANTLR.Allstar.ATN

Methods

prettify :: Edge s nt t -> Pretty Source #

prettifyList :: [Edge s nt t] -> Pretty Source #

(Prettify s, Prettify nt, Prettify t, Hashable nt, Hashable t, Eq nt, Eq t) => Prettify (ATN s nt t) Source # 
Instance details

Defined in Text.ANTLR.Allstar.ATN

Methods

prettify :: ATN s nt t -> Pretty Source #

prettifyList :: [ATN s nt t] -> Pretty Source #

(Prettify t, Prettify ast, Prettify lrstate, Eq t, Eq ast, Eq lrstate, Hashable ast, Hashable t, Hashable lrstate) => Prettify (LRResult lrstate t ast) Source # 
Instance details

Defined in Text.ANTLR.LR

Methods

prettify :: LRResult lrstate t ast -> Pretty Source #

prettifyList :: [LRResult lrstate t ast] -> Pretty Source #

(Prettify lrstate, Prettify nts, Prettify sts, Hashable lrstate, Hashable sts, Hashable nts, Eq lrstate, Eq sts, Eq nts) => Prettify (LRAction nts sts lrstate) Source # 
Instance details

Defined in Text.ANTLR.LR

Methods

prettify :: LRAction nts sts lrstate -> Pretty Source #

prettifyList :: [LRAction nts sts lrstate] -> Pretty Source #

(Prettify a, Prettify nts, Prettify sts) => Prettify (Item a nts sts) Source # 
Instance details

Defined in Text.ANTLR.LR

Methods

prettify :: Item a nts sts -> Pretty Source #

prettifyList :: [Item a nts sts] -> Pretty Source #

(Prettify a, Prettify b, Prettify c, Prettify d) => Prettify (a, b, c, d) Source # 
Instance details

Defined in Text.ANTLR.Pretty

Methods

prettify :: (a, b, c, d) -> Pretty Source #

prettifyList :: [(a, b, c, d)] -> Pretty Source #

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' :: String -> Pretty Source #

Pretty print a literal string by just printing the string.

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.

pChr :: Char -> Pretty Source #

Print a single character to the output.

_doIf :: Monad m => m () -> Bool -> m () Source #

Gets rid of if-then-else lines in the Pretty monad code:

_pIndent :: Pretty Source #

Indent by the number of spaces specified in the state.

_pNewLine :: Pretty Source #

Insert a newline

pshow :: Prettify t => t -> Text Source #

Run the pretty-printer, returning a Text.

pshow' :: Prettify t => t -> String Source #

Run the pretty-printer, returning a String.

pshowIndent :: Prettify t => Int -> t -> Text Source #

Run the pretty-printer with a specific indentation level.

rshow :: Show t => t -> Pretty Source #

Plain-vanilla show of something in the Pretty state monad.

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.

sepBy :: Monad m => m a -> [m ()] -> m () Source #

Pretty-print a list of values, separated by some other pretty-printer.

_sepBy :: Monad m => m a1 -> m a2 -> m b -> m b Source #

Reorder pretty-printer bind.