Safe Haskell | Safe-Inferred |
---|---|
Language | Haskell2010 |
All types.
Synopsis
- data OutputRestriction
- data TypeLayout
- newtype Penalty = Penalty Int
- newtype TabStop = TabStop String
- newtype Printer a = Printer {
- unPrinter :: StateT PrintState (Search Penalty) a
- execPrinter :: Printer a -> PrintState -> Maybe (Penalty, PrintState)
- runPrinter :: Printer a -> PrintState -> Maybe (Penalty, (a, PrintState))
- data PrintState = PrintState {
- psBuffer :: !Buffer
- psIndentLevel :: !Int
- psOnside :: !Int
- psTabStops :: !(Map TabStop Int)
- psConfig :: !Config
- psEolComment :: !Bool
- psOutputRestriction :: !OutputRestriction
- psTypeLayout :: !TypeLayout
- psLine :: PrintState -> Int
- psColumn :: PrintState -> Int
- psNewline :: PrintState -> Bool
- initialPrintState :: Config -> PrintState
- data Config = Config {
- cfgPenalty :: !PenaltyConfig
- cfgAlign :: !AlignConfig
- cfgIndent :: !IndentConfig
- cfgLayout :: !LayoutConfig
- cfgOp :: !OpConfig
- cfgGroup :: !GroupConfig
- cfgOptions :: !OptionConfig
- data SrcSpan = SrcSpan {}
- data CommentType
- data Comment = Comment {
- commentType :: !CommentType
- commentSpan :: !SrcSpan
- commentText :: !String
- data NodeInfo = NodeInfo {}
- noNodeInfo :: NodeInfo
- nodeSpan :: Annotated ast => ast NodeInfo -> SrcSpan
- data Location
Documentation
data OutputRestriction Source #
Instances
Show OutputRestriction Source # | |
Defined in Floskell.Types showsPrec :: Int -> OutputRestriction -> ShowS # show :: OutputRestriction -> String # showList :: [OutputRestriction] -> ShowS # | |
Eq OutputRestriction Source # | |
Defined in Floskell.Types (==) :: OutputRestriction -> OutputRestriction -> Bool # (/=) :: OutputRestriction -> OutputRestriction -> Bool # | |
Ord OutputRestriction Source # | |
Defined in Floskell.Types compare :: OutputRestriction -> OutputRestriction -> Ordering # (<) :: OutputRestriction -> OutputRestriction -> Bool # (<=) :: OutputRestriction -> OutputRestriction -> Bool # (>) :: OutputRestriction -> OutputRestriction -> Bool # (>=) :: OutputRestriction -> OutputRestriction -> Bool # max :: OutputRestriction -> OutputRestriction -> OutputRestriction # min :: OutputRestriction -> OutputRestriction -> OutputRestriction # |
data TypeLayout Source #
Instances
Show TypeLayout Source # | |
Defined in Floskell.Types showsPrec :: Int -> TypeLayout -> ShowS # show :: TypeLayout -> String # showList :: [TypeLayout] -> ShowS # | |
Eq TypeLayout Source # | |
Defined in Floskell.Types (==) :: TypeLayout -> TypeLayout -> Bool # (/=) :: TypeLayout -> TypeLayout -> Bool # | |
Ord TypeLayout Source # | |
Defined in Floskell.Types compare :: TypeLayout -> TypeLayout -> Ordering # (<) :: TypeLayout -> TypeLayout -> Bool # (<=) :: TypeLayout -> TypeLayout -> Bool # (>) :: TypeLayout -> TypeLayout -> Bool # (>=) :: TypeLayout -> TypeLayout -> Bool # max :: TypeLayout -> TypeLayout -> TypeLayout # min :: TypeLayout -> TypeLayout -> TypeLayout # |
A pretty printing monad.
Instances
Alternative Printer Source # | |
Applicative Printer Source # | |
Functor Printer Source # | |
Monad Printer Source # | |
MonadPlus Printer Source # | |
MonadSearch Penalty Printer Source # | |
MonadState PrintState Printer Source # | |
Defined in Floskell.Types get :: Printer PrintState # put :: PrintState -> Printer () # state :: (PrintState -> (a, PrintState)) -> Printer a # |
execPrinter :: Printer a -> PrintState -> Maybe (Penalty, PrintState) Source #
runPrinter :: Printer a -> PrintState -> Maybe (Penalty, (a, PrintState)) Source #
data PrintState Source #
The state of the pretty printer.
PrintState | |
|
Instances
MonadState PrintState Printer Source # | |
Defined in Floskell.Types get :: Printer PrintState # put :: PrintState -> Printer () # state :: (PrintState -> (a, PrintState)) -> Printer a # |
psLine :: PrintState -> Int Source #
psColumn :: PrintState -> Int Source #
psNewline :: PrintState -> Bool Source #
initialPrintState :: Config -> PrintState Source #
Config | |
|
Instances
A portion of the source, spanning one or more lines and zero or more columns.
Instances
Data SrcSpan | |
Defined in Language.Haskell.Exts.SrcLoc gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> SrcSpan -> c SrcSpan # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c SrcSpan # toConstr :: SrcSpan -> Constr # dataTypeOf :: SrcSpan -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c SrcSpan) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c SrcSpan) # gmapT :: (forall b. Data b => b -> b) -> SrcSpan -> SrcSpan # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> SrcSpan -> r # gmapQr :: forall r r'. (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> SrcSpan -> r # gmapQ :: (forall d. Data d => d -> u) -> SrcSpan -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> SrcSpan -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> SrcSpan -> m SrcSpan # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcSpan -> m SrcSpan # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> SrcSpan -> m SrcSpan # | |
Generic SrcSpan | |
Show SrcSpan | |
Eq SrcSpan | |
Ord SrcSpan | |
Defined in Language.Haskell.Exts.SrcLoc | |
Pretty SrcSpan | |
Defined in Language.Haskell.Exts.Pretty prettyPrec :: Int -> SrcSpan -> Doc | |
SrcInfo SrcSpan | |
type Rep SrcSpan | |
Defined in Language.Haskell.Exts.SrcLoc type Rep SrcSpan = D1 ('MetaData "SrcSpan" "Language.Haskell.Exts.SrcLoc" "haskell-src-exts-1.23.1-6RdmxG389EyHsDzuI1Coz2" 'False) (C1 ('MetaCons "SrcSpan" 'PrefixI 'True) ((S1 ('MetaSel ('Just "srcSpanFilename") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 String) :*: S1 ('MetaSel ('Just "srcSpanStartLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int)) :*: (S1 ('MetaSel ('Just "srcSpanStartColumn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: (S1 ('MetaSel ('Just "srcSpanEndLine") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int) :*: S1 ('MetaSel ('Just "srcSpanEndColumn") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Int))))) |
data CommentType Source #
Instances
Show CommentType Source # | |
Defined in Floskell.Types showsPrec :: Int -> CommentType -> ShowS # show :: CommentType -> String # showList :: [CommentType] -> ShowS # |
Comment | |
|
Information for each node in the AST.
NodeInfo | |
|
noNodeInfo :: NodeInfo Source #
Empty NodeInfo
Instances
Bounded Location Source # | |
Enum Location Source # | |
Generic Location Source # | |
Show Location Source # | |
Eq Location Source # | |
Ord Location Source # | |
Defined in Floskell.Config | |
type Rep Location Source # | |