hindent-5.0.1: Extensible Haskell pretty printer

Safe HaskellNone
LanguageHaskell98

HIndent.Types

Description

All types.

Synopsis

Documentation

newtype Printer a Source #

A pretty printing monad.

Constructors

Printer 

Instances

Monad Printer Source # 

Methods

(>>=) :: Printer a -> (a -> Printer b) -> Printer b #

(>>) :: Printer a -> Printer b -> Printer b #

return :: a -> Printer a #

fail :: String -> Printer a #

Functor Printer Source # 

Methods

fmap :: (a -> b) -> Printer a -> Printer b #

(<$) :: a -> Printer b -> Printer a #

Applicative Printer Source # 

Methods

pure :: a -> Printer a #

(<*>) :: Printer (a -> b) -> Printer a -> Printer b #

(*>) :: Printer a -> Printer b -> Printer b #

(<*) :: Printer a -> Printer b -> Printer a #

Alternative Printer Source # 

Methods

empty :: Printer a #

(<|>) :: Printer a -> Printer a -> Printer a #

some :: Printer a -> Printer [a] #

many :: Printer a -> Printer [a] #

MonadPlus Printer Source # 

Methods

mzero :: Printer a #

mplus :: Printer a -> Printer a -> Printer a #

MonadState PrintState Printer Source # 

data PrintState Source #

The state of the pretty printer.

Constructors

PrintState 

Fields

data Config Source #

Configurations shared among the different styles. Styles may pay attention to or completely disregard this configuration.

Constructors

Config 

Fields

defaultConfig :: Config Source #

Default style configuration.

data NodeInfo Source #

Information for each node in the AST.

Constructors

NodeInfo 

Fields

Instances

Data NodeInfo Source # 

Methods

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

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

toConstr :: NodeInfo -> Constr #

dataTypeOf :: NodeInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Show NodeInfo Source # 

data ComInfo Source #

Comment with some more info.

Constructors

ComInfo 

Fields

Instances

Data ComInfo Source # 

Methods

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

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

toConstr :: ComInfo -> Constr #

dataTypeOf :: ComInfo -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ComInfo Source # 

data ComInfoLocation Source #

Comment relative locations.

Constructors

Before 
After 

Instances

Eq ComInfoLocation Source # 
Data ComInfoLocation Source # 

Methods

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

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

toConstr :: ComInfoLocation -> Constr #

dataTypeOf :: ComInfoLocation -> DataType #

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

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

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

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

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

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

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

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

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

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

Show ComInfoLocation Source #