ormolu-0.1.0.0: A formatter for Haskell source code

Safe HaskellNone
LanguageHaskell2010

Ormolu.Parser.CommentStream

Contents

Description

Functions for working with comment stream.

Synopsis

Comment stream

newtype CommentStream Source #

A stream of RealLocated Comments in ascending order with respect to beginning of corresponding spans.

Instances
Eq CommentStream Source # 
Instance details

Defined in Ormolu.Parser.CommentStream

Data CommentStream Source # 
Instance details

Defined in Ormolu.Parser.CommentStream

Methods

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

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

toConstr :: CommentStream -> Constr #

dataTypeOf :: CommentStream -> DataType #

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

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

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

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

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

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

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

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

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

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

Semigroup CommentStream Source # 
Instance details

Defined in Ormolu.Parser.CommentStream

Monoid CommentStream Source # 
Instance details

Defined in Ormolu.Parser.CommentStream

mkCommentStream Source #

Arguments

:: String

Original input

-> [Located String]

Extra comments to include

-> PState

Parser state to use for comment extraction

-> (Maybe (RealLocated Comment), [Shebang], [([RealLocated Comment], Pragma)], CommentStream)

Stack header, shebangs, pragmas, and comment stream

Create CommentStream from PState. The pragmas and shebangs are removed from the CommentStream. Shebangs are only extracted from the comments that come from the first argument.

Comment

data Comment Source #

A wrapper for a single comment. The Bool indicates whether there were atoms before beginning of the comment in the original input. The NonEmpty list inside contains lines of multiline comment {- … -} or just single item/line otherwise.

Constructors

Comment Bool (NonEmpty String) 
Instances
Eq Comment Source # 
Instance details

Defined in Ormolu.Parser.CommentStream

Methods

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

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

Data Comment Source # 
Instance details

Defined in Ormolu.Parser.CommentStream

Methods

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

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

toConstr :: Comment -> Constr #

dataTypeOf :: Comment -> DataType #

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

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

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

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

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

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

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

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

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

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

Show Comment Source # 
Instance details

Defined in Ormolu.Parser.CommentStream

unComment :: Comment -> NonEmpty String Source #

Get a collection of lines from a Comment.

hasAtomsBefore :: Comment -> Bool Source #

Check whether the Comment had some non-whitespace atoms in front of it in the original input.

isMultilineComment :: Comment -> Bool Source #

Is this comment multiline-style?