floskell-0.10.2: A flexible Haskell source code pretty printer

Safe HaskellNone
LanguageHaskell98

Floskell.Types

Description

All types.

Synopsis

Documentation

newtype Penalty Source #

Constructors

Penalty Int 
Instances
Eq Penalty Source # 
Instance details

Defined in Floskell.Types

Methods

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

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

Num Penalty Source # 
Instance details

Defined in Floskell.Types

Ord Penalty Source # 
Instance details

Defined in Floskell.Types

Show Penalty Source # 
Instance details

Defined in Floskell.Types

Semigroup Penalty Source # 
Instance details

Defined in Floskell.Types

Monoid Penalty Source # 
Instance details

Defined in Floskell.Types

MonadSearch Penalty Printer Source # 
Instance details

Defined in Floskell.Types

newtype TabStop Source #

Constructors

TabStop String 
Instances
Eq TabStop Source # 
Instance details

Defined in Floskell.Types

Methods

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

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

Ord TabStop Source # 
Instance details

Defined in Floskell.Types

Show TabStop Source # 
Instance details

Defined in Floskell.Types

newtype Printer a Source #

A pretty printing monad.

Constructors

Printer 
Instances
Monad Printer Source # 
Instance details

Defined in Floskell.Types

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 # 
Instance details

Defined in Floskell.Types

Methods

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

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

Applicative Printer Source # 
Instance details

Defined in Floskell.Types

Methods

pure :: a -> Printer a #

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

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

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

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

Alternative Printer Source # 
Instance details

Defined in Floskell.Types

Methods

empty :: Printer a #

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

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

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

MonadPlus Printer Source # 
Instance details

Defined in Floskell.Types

Methods

mzero :: Printer a #

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

MonadSearch Penalty Printer Source # 
Instance details

Defined in Floskell.Types

MonadState PrintState Printer Source # 
Instance details

Defined in Floskell.Types

data PrintState Source #

The state of the pretty printer.

Constructors

PrintState 

Fields

Instances
MonadState PrintState Printer Source # 
Instance details

Defined in Floskell.Types

data Config Source #

Instances
Generic Config Source # 
Instance details

Defined in Floskell.Config

Associated Types

type Rep Config :: Type -> Type #

Methods

from :: Config -> Rep Config x #

to :: Rep Config x -> Config #

ToJSON Config Source # 
Instance details

Defined in Floskell.Config

FromJSON Config Source # 
Instance details

Defined in Floskell.Config

Default Config Source # 
Instance details

Defined in Floskell.Config

Methods

def :: Config #

type Rep Config Source # 
Instance details

Defined in Floskell.Config

data SrcSpan #

A portion of the source, spanning one or more lines and zero or more columns.

Instances
Eq SrcSpan 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Methods

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

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

Data SrcSpan 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Methods

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 :: (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 #

Ord SrcSpan 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Show SrcSpan 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Generic SrcSpan 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Associated Types

type Rep SrcSpan :: Type -> Type #

Methods

from :: SrcSpan -> Rep SrcSpan x #

to :: Rep SrcSpan x -> SrcSpan #

Pretty SrcSpan 
Instance details

Defined in Language.Haskell.Exts.Pretty

Methods

pretty :: SrcSpan -> Doc

prettyPrec :: Int -> SrcSpan -> Doc

SrcInfo SrcSpan 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

type Rep SrcSpan 
Instance details

Defined in Language.Haskell.Exts.SrcLoc

type Rep SrcSpan = D1 (MetaData "SrcSpan" "Language.Haskell.Exts.SrcLoc" "haskell-src-exts-1.22.0-5tSwDhjCyZb5AQf9d2FsEo" 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 Comment Source #

Instances
Show Comment Source # 
Instance details

Defined in Floskell.Types

data NodeInfo Source #

Information for each node in the AST.

Constructors

NodeInfo 

Fields

Instances
Show NodeInfo Source # 
Instance details

Defined in Floskell.Types

noNodeInfo :: NodeInfo Source #

Empty NodeInfo

data Location Source #

Constructors

Before 
After 
Instances
Bounded Location Source # 
Instance details

Defined in Floskell.Config

Enum Location Source # 
Instance details

Defined in Floskell.Config

Eq Location Source # 
Instance details

Defined in Floskell.Config

Ord Location Source # 
Instance details

Defined in Floskell.Config

Show Location Source # 
Instance details

Defined in Floskell.Config

Generic Location Source # 
Instance details

Defined in Floskell.Config

Associated Types

type Rep Location :: Type -> Type #

Methods

from :: Location -> Rep Location x #

to :: Rep Location x -> Location #

type Rep Location Source # 
Instance details

Defined in Floskell.Config

type Rep Location = D1 (MetaData "Location" "Floskell.Config" "floskell-0.10.2-1uzebgOQCtQ7azD3koQ0G1" False) (C1 (MetaCons "Before" PrefixI False) (U1 :: Type -> Type) :+: C1 (MetaCons "After" PrefixI False) (U1 :: Type -> Type))