language-ninja-0.2.0: A library for dealing with the Ninja build language.

CopyrightCopyright 2017 Awake Security
LicenseApache-2.0
Maintaineropensource@awakesecurity.com
Stabilityexperimental
Safe HaskellNone
LanguageHaskell2010

Language.Ninja.Misc.Located0.1.0

Contents

Description

Tokenize text into a list of non-whitespace chunks, each of which is annotated with its source location.

Synopsis

Located

data Located t Source 0.1.0#

This datatype represents a value annotated with a source location.

Instances

Functor Located  

Methods

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

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

Foldable Located  

Methods

fold :: Monoid m => Located m -> m #

foldMap :: Monoid m => (a -> m) -> Located a -> m #

foldr :: (a -> b -> b) -> b -> Located a -> b #

foldr' :: (a -> b -> b) -> b -> Located a -> b #

foldl :: (b -> a -> b) -> b -> Located a -> b #

foldl' :: (b -> a -> b) -> b -> Located a -> b #

foldr1 :: (a -> a -> a) -> Located a -> a #

foldl1 :: (a -> a -> a) -> Located a -> a #

toList :: Located a -> [a] #

null :: Located a -> Bool #

length :: Located a -> Int #

elem :: Eq a => a -> Located a -> Bool #

maximum :: Ord a => Located a -> a #

minimum :: Ord a => Located a -> a #

sum :: Num a => Located a -> a #

product :: Num a => Located a -> a #

Traversable Located  

Methods

traverse :: Applicative f => (a -> f b) -> Located a -> f (Located b) #

sequenceA :: Applicative f => Located (f a) -> f (Located a) #

mapM :: Monad m => (a -> m b) -> Located a -> m (Located b) #

sequence :: Monad m => Located (m a) -> m (Located a) #

(Monad m, Serial m Text, Serial m t) => Serial m (Located t)

Default Serial instance via Generic.0.1.0

Methods

series :: Series m (Located t) #

(Monad m, CoSerial m Text, CoSerial m t) => CoSerial m (Located t)

Default CoSerial instance via Generic.0.1.0

Methods

coseries :: Series m b -> Series m (Located t -> b) #

Eq t => Eq (Located t)  

Methods

(==) :: Located t -> Located t -> Bool #

(/=) :: Located t -> Located t -> Bool #

Show t => Show (Located t)  

Methods

showsPrec :: Int -> Located t -> ShowS #

show :: Located t -> String #

showList :: [Located t] -> ShowS #

Generic (Located t)  

Associated Types

type Rep (Located t) :: * -> * #

Methods

from :: Located t -> Rep (Located t) x #

to :: Rep (Located t) x -> Located t #

Hashable t => Hashable (Located t)

Default Hashable instance via Generic.0.1.0

Methods

hashWithSalt :: Int -> Located t -> Int #

hash :: Located t -> Int #

ToJSON t => ToJSON (Located t)

Converts to {position: …, value: …}.0.1.0

FromJSON t => FromJSON (Located t)

Inverse of the ToJSON instance.0.1.0

NFData t => NFData (Located t)

Default NFData instance via Generic.0.1.0

Methods

rnf :: Located t -> () #

type Rep (Located t)  
type Rep (Located t) = D1 (MetaData "Located" "Language.Ninja.Misc.Located" "language-ninja-0.2.0-4aVVODOvkNMFxGcRpnztag" False) (C1 (MetaCons "MkLocated" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_locatedPos") SourceUnpack SourceStrict DecidedUnpack) (Rec0 Position)) (S1 (MetaSel (Just Symbol "_locatedVal") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 t))))

tokenize :: Maybe Path -> Text -> [Located Text] Source 0.1.0#

Given path :: Maybe Path and a text :: Text, do the following:

  • Remove all '\r' characters from the text.
  • Split the text into chunks that are guaranteed not to contain newlines or whitespace, and which are annotated with their location.

tokenizeFile :: MonadReadFile m => Path -> m [Located Text] Source 0.1.0#

Read the file at the given Path and then run tokenize on the resulting Text.

tokenizeText :: Text -> [Located Text] Source 0.1.0#

This function is equivalent to tokenize Nothing.

locatedPos :: Lens' (Located t) Position Source 0.1.0#

The position of this located value.

locatedVal :: Lens' (Located t) t Source 0.1.0#

The value underlying this located value.

Spans

data Spans Source 0.1.0#

A type representing a set of source spans.

Instances

Eq Spans  

Methods

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

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

Show Spans  

Methods

showsPrec :: Int -> Spans -> ShowS #

show :: Spans -> String #

showList :: [Spans] -> ShowS #

Generic Spans  

Associated Types

type Rep Spans :: * -> * #

Methods

from :: Spans -> Rep Spans x #

to :: Rep Spans x -> Spans #

Semigroup Spans  

Methods

(<>) :: Spans -> Spans -> Spans #

sconcat :: NonEmpty Spans -> Spans #

stimes :: Integral b => b -> Spans -> Spans #

Monoid Spans  

Methods

mempty :: Spans #

mappend :: Spans -> Spans -> Spans #

mconcat :: [Spans] -> Spans #

Hashable Spans  

Methods

hashWithSalt :: Int -> Spans -> Int #

hash :: Spans -> Int #

ToJSON Spans  
FromJSON Spans  
NFData Spans  

Methods

rnf :: Spans -> () #

(Monad m, Serial m (HashSet Span)) => Serial m Spans

Default Serial instance via Generic.0.1.0

Methods

series :: Series m Spans #

(Monad m, CoSerial m (HashSet Span)) => CoSerial m Spans

Default CoSerial instance via Generic.0.1.0

Methods

coseries :: Series m b -> Series m (Spans -> b) #

type Rep Spans  
type Rep Spans = D1 (MetaData "Spans" "Language.Ninja.Misc.Located" "language-ninja-0.2.0-4aVVODOvkNMFxGcRpnztag" True) (C1 (MetaCons "MkSpans" PrefixI False) (S1 (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 (HashSet Span))))

makeSpans :: [Span] -> Spans Source 0.1.0#

Construct a Spans from a list of Spans.

spansSet :: Iso' Spans (HashSet Span) Source 0.1.0#

A lens into the HashSet Span underlying a value of type Spans.

Span

data Span Source 0.1.0#

Represents a span of source code.

Instances

Eq Span  

Methods

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

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

Show Span  

Methods

showsPrec :: Int -> Span -> ShowS #

show :: Span -> String #

showList :: [Span] -> ShowS #

Generic Span  

Associated Types

type Rep Span :: * -> * #

Methods

from :: Span -> Rep Span x #

to :: Rep Span x -> Span #

Hashable Span

Default Hashable instance via Generic.0.1.0

Methods

hashWithSalt :: Int -> Span -> Int #

hash :: Span -> Int #

ToJSON Span

Converts to {file: …, start: …, end: …}.0.1.0

FromJSON Span

Inverse of the ToJSON instance.0.1.0

NFData Span

Default NFData instance via Generic.0.1.0

Methods

rnf :: Span -> () #

(Monad m, Serial m Text) => Serial m Span

Default Serial instance via Generic.0.1.0

Methods

series :: Series m Span #

(Monad m, CoSerial m Text) => CoSerial m Span

Default CoSerial instance via Generic.0.1.0

Methods

coseries :: Series m b -> Series m (Span -> b) #

type Rep Span  

makeSpan Source 0.1.0#

Arguments

:: Maybe Path

The file in which this span resides, if any.

-> Offset

The start offset.

-> Offset

The end offset.

-> Span 

Construct a Span from a given start position to a given end position.

spanPath :: Lens' Span (Maybe Path) Source 0.1.0#

A lens into the (nullable) path associated with a Span.

spanRange :: Lens' Span (Offset, Offset) Source 0.1.0#

A lens giving the start and end Offsets associated with a Span.

spanStart :: Lens' Span Offset Source 0.1.0#

A lens into the Offset associated with the start of a Span.

spanEnd :: Lens' Span Offset Source 0.1.0#

A lens into the Offset associated with the end of a Span.

spanStartPos :: Getter Span Position Source 0.1.0#

A getter for the Position associated with the start of a Span.

spanEndPos :: Getter Span Position Source 0.1.0#

A getter for the Position associated with the end of a Span.

Position

data Position Source 0.1.0#

This datatype represents the position of a cursor in a text file.

Instances

Eq Position  
Show Position  
Generic Position  

Associated Types

type Rep Position :: * -> * #

Methods

from :: Position -> Rep Position x #

to :: Rep Position x -> Position #

Hashable Position

Default Hashable instance via Generic.0.1.0

Methods

hashWithSalt :: Int -> Position -> Int #

hash :: Position -> Int #

ToJSON Position

Converts to {file: …, line: …, col: …}.0.1.0

FromJSON Position

Inverse of the ToJSON instance.0.1.0

NFData Position

Default NFData instance via Generic.0.1.0

Methods

rnf :: Position -> () #

(Monad m, Serial m Text) => Serial m Position

Default Serial instance via Generic.0.1.0

Methods

series :: Series m Position #

(Monad m, CoSerial m Text) => CoSerial m Position

Default CoSerial instance via Generic.0.1.0

Methods

coseries :: Series m b -> Series m (Position -> b) #

type Rep Position  
type Rep Position = D1 (MetaData "Position" "Language.Ninja.Misc.Located" "language-ninja-0.2.0-4aVVODOvkNMFxGcRpnztag" False) (C1 (MetaCons "MkPosition" PrefixI True) ((:*:) (S1 (MetaSel (Just Symbol "_positionFile") NoSourceUnpackedness SourceStrict DecidedStrict) (Rec0 (Maybe Path))) ((:*:) (S1 (MetaSel (Just Symbol "_positionLine") SourceUnpack SourceStrict DecidedUnpack) (Rec0 Line)) (S1 (MetaSel (Just Symbol "_positionCol") SourceUnpack SourceStrict DecidedUnpack) (Rec0 Column)))))

makePosition :: Maybe Path -> Offset -> Position Source 0.1.0#

Construct a Position from a (nullable) path and a (line, column) pair.

positionFile :: Lens' Position (Maybe Path) Source 0.1.0#

The path of the file pointed to by this position, if any.

positionOffset :: Lens' Position Offset Source 0.1.0#

The offset in the file pointed to by this position.

positionLine :: Lens' Position Line Source 0.1.0#

The line number in the file pointed to by this position.

positionCol :: Lens' Position Column Source 0.1.0#

The column number in the line pointed to by this position.

comparePosition :: Position -> Position -> Maybe Ordering Source 0.1.0#

If two Positions are comparable (i.e.: if they are in the same file), this function will return an Ordering giving their relative positions. Otherwise, it will of course return Nothing.

Offset

type Offset = (Line, Column) Source 0.1.0#

A line/column offset into a file.

compareOffset :: Offset -> Offset -> Ordering Source 0.1.0#

Compare two Offsets in lexicographic order (i.e.: the Column is ignored unless they are on the same Line).

offsetLine :: Lens' Offset Line Source 0.1.0#

A lens into the Line associated with an Offset.

For now, this is simply defined as offsetLine = _1, but if Offset is later refactored to be an abstract data type, using this lens instead of _1 will decrease the amount of code that breaks.

offsetColumn :: Lens' Offset Column Source 0.1.0#

A lens into the Line associated with an Offset.

Read the description of offsetLine for an understanding of why this exists and why you should use it instead of _2.

Miscellaneous

type Line = Int Source 0.1.0#

A line number.

type Column = Int Source 0.1.0#

A column number.