haskell-src-exts-1.23.1: Manipulating Haskell source: abstract syntax, lexer, parser, and pretty-printer
Copyright (c) Niklas Broberg 2009
License BSD-style (see the file LICENSE.txt)
Maintainer Niklas Broberg, d00nibro@chalmers.se
Stability stable
Portability portable
Safe Haskell Safe-Inferred
Language Haskell98

Language.Haskell.Exts.SrcLoc

Description

This module defines various data types representing source location information, of varying degree of preciseness.

Synopsis

Documentation

data SrcLoc Source #

A single position in the source.

Instances

Instances details
Eq SrcLoc Source #
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Data SrcLoc Source #
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) -> SrcLoc -> c SrcLoc Source #

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

toConstr :: SrcLoc -> Constr Source #

dataTypeOf :: SrcLoc -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord SrcLoc Source #
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Show SrcLoc Source #
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Generic SrcLoc Source #
Instance details

Defined in Language.Haskell.Exts.SrcLoc

SrcInfo SrcLoc Source #
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Pretty SrcLoc Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

type Rep SrcLoc Source #
Instance details

Defined in Language.Haskell.Exts.SrcLoc

data SrcSpan Source #

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

Instances

Instances details
Eq SrcSpan Source #
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Data SrcSpan Source #
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 Source #

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

toConstr :: SrcSpan -> Constr Source #

dataTypeOf :: SrcSpan -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord SrcSpan Source #
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Show SrcSpan Source #
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Generic SrcSpan Source #
Instance details

Defined in Language.Haskell.Exts.SrcLoc

SrcInfo SrcSpan Source #
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Pretty SrcSpan Source #
Instance details

Defined in Language.Haskell.Exts.Pretty

type Rep SrcSpan Source #
Instance details

Defined in Language.Haskell.Exts.SrcLoc

mkSrcSpan :: SrcLoc -> SrcLoc -> SrcSpan Source #

Combine two locations in the source to denote a span.

mergeSrcSpan :: SrcSpan -> SrcSpan -> SrcSpan Source #

Merge two source spans into a single span from the start of the first to the end of the second. Assumes that the two spans relate to the same source file.

isNullSpan :: SrcSpan -> Bool Source #

Test if a given span starts and ends at the same location.

data Loc a Source #

An entity located in the source.

Constructors

Loc

Instances

Instances details
Eq a => Eq ( Loc a) Source #
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Ord a => Ord ( Loc a) Source #
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Show a => Show ( Loc a) Source #
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Generic ( Loc a) Source #
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Associated Types

type Rep ( Loc a) :: Type -> Type Source #

type Rep ( Loc a) Source #
Instance details

Defined in Language.Haskell.Exts.SrcLoc

data SrcSpanInfo Source #

A portion of the source, extended with information on the position of entities within the span.

Instances

Instances details
Eq SrcSpanInfo Source #
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Data SrcSpanInfo Source #
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) -> SrcSpanInfo -> c SrcSpanInfo Source #

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

toConstr :: SrcSpanInfo -> Constr Source #

dataTypeOf :: SrcSpanInfo -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord SrcSpanInfo Source #
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Show SrcSpanInfo Source #
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Generic SrcSpanInfo Source #
Instance details

Defined in Language.Haskell.Exts.SrcLoc

SrcInfo SrcSpanInfo Source #
Instance details

Defined in Language.Haskell.Exts.SrcLoc

Parseable ( Stmt SrcSpanInfo ) Source #
Instance details

Defined in Language.Haskell.Exts.Parser

Parseable ( Pat SrcSpanInfo ) Source #
Instance details

Defined in Language.Haskell.Exts.Parser

Parseable ( Exp SrcSpanInfo ) Source #
Instance details

Defined in Language.Haskell.Exts.Parser

Parseable ( Type SrcSpanInfo ) Source #
Instance details

Defined in Language.Haskell.Exts.Parser

Parseable ( Decl SrcSpanInfo ) Source #
Instance details

Defined in Language.Haskell.Exts.Parser

Parseable ( ImportDecl SrcSpanInfo ) Source #
Instance details

Defined in Language.Haskell.Exts.Parser

Parseable ( Module SrcSpanInfo ) Source #
Instance details

Defined in Language.Haskell.Exts.Parser

Parseable ( NonGreedy ( ListOf ( ModulePragma SrcSpanInfo ))) Source #
Instance details

Defined in Language.Haskell.Exts.Parser

Parseable ( NonGreedy ( ModuleHeadAndImports SrcSpanInfo )) Source #
Instance details

Defined in Language.Haskell.Exts.Parser

Parseable ( NonGreedy ( PragmasAndModuleHead SrcSpanInfo )) Source #
Instance details

Defined in Language.Haskell.Exts.Parser

Parseable ( NonGreedy ( PragmasAndModuleName SrcSpanInfo )) Source #
Instance details

Defined in Language.Haskell.Exts.Parser

type Rep SrcSpanInfo Source #
Instance details

Defined in Language.Haskell.Exts.SrcLoc

type Rep SrcSpanInfo = D1 (' MetaData "SrcSpanInfo" "Language.Haskell.Exts.SrcLoc" "haskell-src-exts-1.23.1-LTqMCpSQH9m4ymWElpQTPo" ' False ) ( C1 (' MetaCons "SrcSpanInfo" ' PrefixI ' True ) ( S1 (' MetaSel (' Just "srcInfoSpan") ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 SrcSpan ) :*: S1 (' MetaSel (' Just "srcInfoPoints") ' NoSourceUnpackedness ' NoSourceStrictness ' DecidedLazy ) ( Rec0 [ SrcSpan ])))

noInfoSpan :: SrcSpan -> SrcSpanInfo Source #

Generate a SrcSpanInfo with no positional information for entities.

noSrcSpan :: SrcSpanInfo Source #

A bogus SrcSpanInfo , the location is noLoc . `noSrcSpan = noInfoSpan (mkSrcSpan noLoc noLoc)`

infoSpan :: SrcSpan -> [ SrcSpan ] -> SrcSpanInfo Source #

Generate a SrcSpanInfo with the supplied positional information for entities.

combSpanInfo :: SrcSpanInfo -> SrcSpanInfo -> SrcSpanInfo Source #

Combine two SrcSpanInfo s into one that spans the combined source area of the two arguments, leaving positional information blank.

(<+?>) :: SrcSpanInfo -> Maybe SrcSpanInfo -> SrcSpanInfo infixl 4 Source #

Optionally combine the first argument with the second, or return it unchanged if the second argument is Nothing .

(<?+>) :: Maybe SrcSpanInfo -> SrcSpanInfo -> SrcSpanInfo infixl 4 Source #

Optionally combine the second argument with the first, or return it unchanged if the first argument is Nothing .

(<**) :: SrcSpanInfo -> [ SrcSpan ] -> SrcSpanInfo infixl 4 Source #

Add more positional information for entities of a span.

(<^^>) :: SrcSpan -> SrcSpan -> SrcSpanInfo infixl 6 Source #

Merge two SrcSpan s and lift them to a SrcInfoSpan with no positional information for entities.

class SrcInfo si where Source #

A class to work over all kinds of source location information.