update-nix-fetchgit-0.2.5: A program to update fetchgit values in Nix expressions
Safe HaskellNone
LanguageHaskell2010

Update.Span

Description

This module deals with updating spans of characters in values of type Text.

It defines some helper types and functions to apply these "updates".

Synopsis

Documentation

data SpanUpdate Source #

A span and some text to replace it with. They don't have to be the same length.

Instances

Instances details
Data SpanUpdate Source # 
Instance details

Defined in Update.Span

Methods

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

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

toConstr :: SpanUpdate -> Constr #

dataTypeOf :: SpanUpdate -> DataType #

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

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

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

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

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

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

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

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

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

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

Show SpanUpdate Source # 
Instance details

Defined in Update.Span

data SrcSpan #

A location in a source file

Constructors

SrcSpan 

Instances

Instances details
Eq SrcSpan 
Instance details

Defined in Nix.Expr.Types.Annotated

Methods

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

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

Data SrcSpan 
Instance details

Defined in Nix.Expr.Types.Annotated

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 :: forall r r'. (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 Nix.Expr.Types.Annotated

Show SrcSpan 
Instance details

Defined in Nix.Expr.Types.Annotated

Generic SrcSpan 
Instance details

Defined in Nix.Expr.Types.Annotated

Associated Types

type Rep SrcSpan :: Type -> Type #

Methods

from :: SrcSpan -> Rep SrcSpan x #

to :: Rep SrcSpan x -> SrcSpan #

Semigroup SrcSpan 
Instance details

Defined in Nix.Expr.Types.Annotated

Hashable SrcSpan 
Instance details

Defined in Nix.Expr.Types.Annotated

Methods

hashWithSalt :: Int -> SrcSpan -> Int #

hash :: SrcSpan -> Int #

ToJSON SrcSpan 
Instance details

Defined in Nix.Expr.Types.Annotated

FromJSON SrcSpan 
Instance details

Defined in Nix.Expr.Types.Annotated

Binary NExprLoc 
Instance details

Defined in Nix.Expr.Types.Annotated

Methods

put :: NExprLoc -> Put #

get :: Get NExprLoc #

putList :: [NExprLoc] -> Put #

Binary SrcSpan 
Instance details

Defined in Nix.Expr.Types.Annotated

Methods

put :: SrcSpan -> Put #

get :: Get SrcSpan #

putList :: [SrcSpan] -> Put #

NFData SrcSpan 
Instance details

Defined in Nix.Expr.Types.Annotated

Methods

rnf :: SrcSpan -> () #

ToExpr NExprLoc 
Instance details

Defined in Nix.TH

Methods

toExpr :: NExprLoc -> NExprLoc #

Serialise NExprLoc 
Instance details

Defined in Nix.Expr.Types.Annotated

Serialise SrcSpan 
Instance details

Defined in Nix.Expr.Types.Annotated

Binary r => Binary (NExprLocF r) 
Instance details

Defined in Nix.Expr.Types.Annotated

Methods

put :: NExprLocF r -> Put #

get :: Get (NExprLocF r) #

putList :: [NExprLocF r] -> Put #

Serialise r => Serialise (Compose (Ann SrcSpan) NExprF r) 
Instance details

Defined in Nix.Expr.Types.Annotated

type Rep SrcSpan 
Instance details

Defined in Nix.Expr.Types.Annotated

type Rep SrcSpan = D1 ('MetaData "SrcSpan" "Nix.Expr.Types.Annotated" "hnix-0.11.0-HCVhUmIJlUZ32fis3dm6v2" 'False) (C1 ('MetaCons "SrcSpan" 'PrefixI 'True) (S1 ('MetaSel ('Just "spanBegin") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourcePos) :*: S1 ('MetaSel ('Just "spanEnd") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 SourcePos)))

data SourcePos #

The data type SourcePos represents source positions. It contains the name of the source file, a line number, and a column number. Source line and column positions change intensively during parsing, so we need to make them strict to avoid memory leaks.

Constructors

SourcePos 

Fields

Instances

Instances details
Eq SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Data SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Methods

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

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

toConstr :: SourcePos -> Constr #

dataTypeOf :: SourcePos -> DataType #

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

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

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

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

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

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

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

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

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

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

Ord SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Read SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Show SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Generic SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Associated Types

type Rep SourcePos :: Type -> Type #

NFData SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

Methods

rnf :: SourcePos -> () #

type Rep SourcePos 
Instance details

Defined in Text.Megaparsec.Pos

type Rep SourcePos = D1 ('MetaData "SourcePos" "Text.Megaparsec.Pos" "megaparsec-8.0.0-9Vrm0rkChK0Lp6QBTm2WWZ" 'False) (C1 ('MetaCons "SourcePos" 'PrefixI 'True) (S1 ('MetaSel ('Just "sourceName") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 FilePath) :*: (S1 ('MetaSel ('Just "sourceLine") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Pos) :*: S1 ('MetaSel ('Just "sourceColumn") 'NoSourceUnpackedness 'SourceStrict 'DecidedUnpack) (Rec0 Pos))))

updateSpan :: SpanUpdate -> Text -> Text Source #

Update a single span of characters inside a text value. If you're updating multiples spans it's best to use updateSpans.

updateSpans :: [SpanUpdate] -> Text -> Text Source #

Update many spans in a file. They must be non-overlapping.

linearizeSourcePos Source #

Arguments

:: Text

The string to linearize in

-> Int64

The line offset

-> Int64

The column offset

-> Int64

The character offset

Go from a line and column representation to a single character offset from the beginning of the text.

This probably fails on crazy texts with multi character line breaks.

split :: SourcePos -> Text -> (Text, Text) Source #

Split some text at a particular SourcePos