Safe Haskell | None |
---|---|
Language | Haskell2010 |
Synopsis
- newtype Printer a = Printer (ReaderT PrinterConfig (State PrinterState) a)
- data PrinterConfig = PrinterConfig {}
- data PrinterState = PrinterState {
- lines :: !Lines
- linePos :: !Int
- currentLine :: !String
- pendingComments :: ![RealLocated AnnotationComment]
- parsedModule :: !Module
- type P = Printer
- runPrinter :: PrinterConfig -> [RealLocated AnnotationComment] -> Module -> Printer a -> (a, Lines)
- runPrinter_ :: PrinterConfig -> [RealLocated AnnotationComment] -> Module -> Printer a -> Lines
- comma :: P ()
- dot :: P ()
- getAnnot :: SrcSpan -> P [AnnKeywordId]
- getCurrentLine :: P String
- getCurrentLineLength :: P Int
- getDocstrPrev :: SrcSpan -> P (Maybe AnnotationComment)
- newline :: P ()
- parenthesize :: P a -> P a
- peekNextCommentPos :: P (Maybe SrcSpan)
- prefix :: P a -> P b -> P b
- putComment :: AnnotationComment -> P ()
- putEolComment :: SrcSpan -> P ()
- putOutputable :: Outputable a => a -> P ()
- putAllSpanComments :: P () -> SrcSpan -> P ()
- putCond :: (PrinterState -> Bool) -> P b -> P b -> P b
- putType :: Located (HsType GhcPs) -> P ()
- putRdrName :: Located RdrName -> P ()
- putText :: String -> P ()
- removeCommentTo :: SrcSpan -> P [AnnotationComment]
- removeCommentToEnd :: SrcSpan -> P [AnnotationComment]
- removeLineComment :: Int -> P (Maybe AnnotationComment)
- sep :: P a -> [P a] -> P ()
- groupAttachedComments :: [Located a] -> P [([AnnotationComment], NonEmpty (Located a))]
- space :: P ()
- spaces :: Int -> P ()
- suffix :: P a -> P b -> P a
- pad :: Int -> P ()
- withColumns :: Maybe Int -> P a -> P a
- modifyCurrentLine :: (String -> String) -> P ()
- wrapping :: P a -> P a -> P a
Documentation
Printer that keeps state of file
Instances
Monad Printer Source # | |
Functor Printer Source # | |
Applicative Printer Source # | |
MonadState PrinterState Printer Source # | |
Defined in Language.Haskell.Stylish.Printer get :: Printer PrinterState # put :: PrinterState -> Printer () # state :: (PrinterState -> (a, PrinterState)) -> Printer a # | |
MonadReader PrinterConfig Printer Source # | |
Defined in Language.Haskell.Stylish.Printer ask :: Printer PrinterConfig # local :: (PrinterConfig -> PrinterConfig) -> Printer a -> Printer a # reader :: (PrinterConfig -> a) -> Printer a # |
data PrinterConfig Source #
Configuration for printer, currently empty
Instances
MonadReader PrinterConfig Printer Source # | |
Defined in Language.Haskell.Stylish.Printer ask :: Printer PrinterConfig # local :: (PrinterConfig -> PrinterConfig) -> Printer a -> Printer a # reader :: (PrinterConfig -> a) -> Printer a # |
data PrinterState Source #
State of printer
PrinterState | |
|
Instances
MonadState PrinterState Printer Source # | |
Defined in Language.Haskell.Stylish.Printer get :: Printer PrinterState # put :: PrinterState -> Printer () # state :: (PrinterState -> (a, PrinterState)) -> Printer a # |
Alias
Functions to use the printer
runPrinter :: PrinterConfig -> [RealLocated AnnotationComment] -> Module -> Printer a -> (a, Lines) Source #
Run printer to get printed lines out of module as well as return value of monad
runPrinter_ :: PrinterConfig -> [RealLocated AnnotationComment] -> Module -> Printer a -> Lines Source #
Run printer to get printed lines only
Combinators
getCurrentLine :: P String Source #
Get current line
getCurrentLineLength :: P Int Source #
Get current line length
getDocstrPrev :: SrcSpan -> P (Maybe AnnotationComment) Source #
Get a docstring on the start line of SrcSpan
that is a -- ^
comment
parenthesize :: P a -> P a Source #
Add parens around a printed action
putComment :: AnnotationComment -> P () Source #
Print any comment
putEolComment :: SrcSpan -> P () Source #
Given the current start line of SrcSpan
, remove and put EOL comment for same line
putOutputable :: Outputable a => a -> P () Source #
Print an Outputable
putAllSpanComments :: P () -> SrcSpan -> P () Source #
Put all comments that has positions within SrcSpan
and separate by
passed P ()
putCond :: (PrinterState -> Bool) -> P b -> P b -> P b Source #
Check condition post action, and use fallback if false
removeCommentTo :: SrcSpan -> P [AnnotationComment] Source #
Removes comments from the state up to start line of SrcSpan
and returns
the ones that were removed
removeCommentToEnd :: SrcSpan -> P [AnnotationComment] Source #
Removes comments from the state up to end line of SrcSpan
and returns
the ones that were removed
removeLineComment :: Int -> P (Maybe AnnotationComment) Source #
Gets comment on supplied line
and removes it from the state
groupAttachedComments :: [Located a] -> P [([AnnotationComment], NonEmpty (Located a))] Source #
Get attached comments belonging to '[Located a]' given
Indent to a given number of spaces. If the current line already exceeds that number in length, nothing happens.