brittany-0.8.0.2: Haskell source code formatter

Safe HaskellNone
LanguageHaskell2010

Language.Haskell.Brittany.Internal.Types

Documentation

data LayoutState Source #

Constructors

LayoutState 

Fields

  • _lstate_baseYs :: [Int]

    stack of number of current indentation columns (not number of indentations).

  • _lstate_curYOrAddNewline :: Either Int Int

    Either: 1) number of chars in the current line. 2) number of newlines to be inserted before inserting any non-space elements.

  • _lstate_indLevels :: [Int]

    stack of current indentation levels. set for any layout-affected elements such as letdocase/where elements. The main purpose of this member is to properly align comments, as their annotation positions are relative to the current layout indentation level.

  • _lstate_indLevelLinger :: Int
     
  • _lstate_comments :: Anns
     
  • _lstate_commentCol :: Maybe Int
     
  • _lstate_addSepSpace :: Maybe Int
     
  • _lstate_inhibitMTEL :: Bool

    inhibit move-to-exact-location. normally, processing a node's annotation involves moving to the exact (vertical) location of the node. this ensures that newlines in the input are retained in the output. While this flag is on, this behaviour will be disabled. The flag is automatically turned off when inserting any kind of newline. , _lstate_isNewline :: NewLineState -- captures if the layouter currently is in a new line, i.e. if the -- current line only contains (indentation) spaces.

data BrittanyError Source #

Constructors

ErrorInput String

parsing failed

ErrorUnusedComment String

internal error: some comment went missing

LayoutWarning String

some warning

Data ast => ErrorUnknownNode String ast

internal error: pretty-printing is not implemented for type of node in the syntax-tree

ErrorOutputCheck

checking the output for syntactic validity failed

data ColSig Source #

Instances

Eq ColSig Source # 

Methods

(==) :: ColSig -> ColSig -> Bool #

(/=) :: ColSig -> ColSig -> Bool #

Data ColSig Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> ColSig -> c ColSig #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c ColSig #

toConstr :: ColSig -> Constr #

dataTypeOf :: ColSig -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c ColSig) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c ColSig) #

gmapT :: (forall b. Data b => b -> b) -> ColSig -> ColSig #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> ColSig -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> ColSig -> r #

gmapQ :: (forall d. Data d => d -> u) -> ColSig -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> ColSig -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> ColSig -> m ColSig #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> ColSig -> m ColSig #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> ColSig -> m ColSig #

Ord ColSig Source # 
Show ColSig Source # 

data BrIndent Source #

Instances

Eq BrIndent Source # 
Data BrIndent Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BrIndent -> c BrIndent #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BrIndent #

toConstr :: BrIndent -> Constr #

dataTypeOf :: BrIndent -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BrIndent) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BrIndent) #

gmapT :: (forall b. Data b => b -> b) -> BrIndent -> BrIndent #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BrIndent -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BrIndent -> r #

gmapQ :: (forall d. Data d => d -> u) -> BrIndent -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BrIndent -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BrIndent -> m BrIndent #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BrIndent -> m BrIndent #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BrIndent -> m BrIndent #

Ord BrIndent Source # 
Show BrIndent Source # 

type ToBriDocC sym c = Located sym -> ToBriDocM c Source #

data BriDoc Source #

Instances

Eq BriDoc Source # 

Methods

(==) :: BriDoc -> BriDoc -> Bool #

(/=) :: BriDoc -> BriDoc -> Bool #

Data BriDoc Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BriDoc -> c BriDoc #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c BriDoc #

toConstr :: BriDoc -> Constr #

dataTypeOf :: BriDoc -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c BriDoc) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c BriDoc) #

gmapT :: (forall b. Data b => b -> b) -> BriDoc -> BriDoc #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BriDoc -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BriDoc -> r #

gmapQ :: (forall d. Data d => d -> u) -> BriDoc -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BriDoc -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BriDoc -> m BriDoc #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BriDoc -> m BriDoc #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BriDoc -> m BriDoc #

Ord BriDoc Source # 
Uniplate BriDoc Source # 

Methods

uniplate :: BriDoc -> (Str BriDoc, Str BriDoc -> BriDoc) #

descend :: (BriDoc -> BriDoc) -> BriDoc -> BriDoc #

descendM :: Monad m => (BriDoc -> m BriDoc) -> BriDoc -> m BriDoc #

data BriDocF f Source #

Instances

Data (BriDocF ((,) Int)) Source # 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> BriDocF ((,) Int) -> c (BriDocF ((,) Int)) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (BriDocF ((,) Int)) #

toConstr :: BriDocF ((,) Int) -> Constr #

dataTypeOf :: BriDocF ((,) Int) -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (BriDocF ((,) Int))) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (BriDocF ((,) Int))) #

gmapT :: (forall b. Data b => b -> b) -> BriDocF ((,) Int) -> BriDocF ((,) Int) #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> BriDocF ((,) Int) -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> BriDocF ((,) Int) -> r #

gmapQ :: (forall d. Data d => d -> u) -> BriDocF ((,) Int) -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> BriDocF ((,) Int) -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> BriDocF ((,) Int) -> m (BriDocF ((,) Int)) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> BriDocF ((,) Int) -> m (BriDocF ((,) Int)) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> BriDocF ((,) Int) -> m (BriDocF ((,) Int)) #

pattern LineModeValid :: forall t. t -> LineModeValidity t Source #

pattern LineModeInvalid :: forall t. LineModeValidity t Source #