Copyright | (c) Alec Theriault 2017-2018 |
---|---|
License | BSD-style |
Maintainer | alec.theriault@gmail.com |
Stability | experimental |
Portability | GHC |
Safe Haskell | None |
Language | Haskell2010 |
Everything to do with describing a position or a contiguous region in a file.
Synopsis
- data Position
- = Position { }
- | NoPosition
- prettyPosition :: Position -> String
- maxPos :: Position -> Position -> Position
- minPos :: Position -> Position -> Position
- initPos :: Position
- incPos :: Position -> Int -> Position
- retPos :: Position -> Position
- incOffset :: Position -> Int -> Position
- data Span = Span {}
- unspan :: Spanned a -> a
- prettySpan :: Span -> String
- subsetOf :: Span -> Span -> Bool
- (#) :: (Located a, Located b) => a -> b -> Span
- data Spanned a = Spanned a !Span
- class Located a where
Positions in files
A position in a source file. The row and column information is kept only for its convenience and human-readability. Analogous to the information encoded in a cursor.
Instances
Eq Position Source # | |
Data Position Source # | |
Defined in Language.Rust.Data.Position gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Position -> c Position # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Position # toConstr :: Position -> Constr # dataTypeOf :: Position -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Position) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Position) # gmapT :: (forall b. Data b => b -> b) -> Position -> Position # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Position -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Position -> r # gmapQ :: (forall d. Data d => d -> u) -> Position -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Position -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Position -> m Position # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Position -> m Position # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Position -> m Position # | |
Ord Position Source # | |
Defined in Language.Rust.Data.Position | |
Show Position Source # | Field names are not shown |
Generic Position Source # | |
NFData Position Source # | |
Defined in Language.Rust.Data.Position | |
Pretty Position Source # | |
Defined in Language.Rust.Pretty prettyUnresolved :: Position -> Doc b Source # | |
type Rep Position Source # | |
Defined in Language.Rust.Data.Position type Rep Position = D1 (MetaData "Position" "Language.Rust.Data.Position" "flp-0.1.0.0-DeMkA8gwwJbCOh6gqZDp9v" False) (C1 (MetaCons "Position" PrefixI True) (S1 (MetaSel (Just "absoluteOffset") SourceUnpack SourceStrict DecidedStrict) (Rec0 Int) :*: (S1 (MetaSel (Just "row") SourceUnpack SourceStrict DecidedStrict) (Rec0 Int) :*: S1 (MetaSel (Just "col") SourceUnpack SourceStrict DecidedStrict) (Rec0 Int))) :+: C1 (MetaCons "NoPosition" PrefixI False) (U1 :: Type -> Type)) |
maxPos :: Position -> Position -> Position Source #
Maximum of two positions, bias for actual positions.
>>>
maxPos (Position 30 5 8) (Position 37 5 15)
Position 37 5 15
>>>
maxPos NoPosition (Position 30 5 8)
Position 30 5 8
minPos :: Position -> Position -> Position Source #
Maximum and minimum positions, bias for actual positions.
>>>
minPos (Position 30 5 8) (Position 37 5 15)
Position 30 5 8
>>>
minPos NoPosition (Position 30 5 8)
Position 30 5 8
incOffset :: Position -> Int -> Position Source #
Advance only the absolute offset, not the row and column information. Only use this if you know what you are doing!
Spans in files
Spans represent a contiguous region of code, delimited by two Position
s. The endpoints are
inclusive. Analogous to the information encoded in a selection.
Instances
A "tagging" of something with a Span
that describes its extent.
Instances
Monad Spanned Source # | |
Functor Spanned Source # | |
Applicative Spanned Source # | |
Eq a => Eq (Spanned a) Source # | |
Data a => Data (Spanned a) Source # | |
Defined in Language.Rust.Data.Position gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Spanned a -> c (Spanned a) # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Spanned a) # toConstr :: Spanned a -> Constr # dataTypeOf :: Spanned a -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c (Spanned a)) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Spanned a)) # gmapT :: (forall b. Data b => b -> b) -> Spanned a -> Spanned a # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Spanned a -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Spanned a -> r # gmapQ :: (forall d. Data d => d -> u) -> Spanned a -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Spanned a -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Spanned a -> m (Spanned a) # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Spanned a -> m (Spanned a) # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Spanned a -> m (Spanned a) # | |
Ord a => Ord (Spanned a) Source # | |
Defined in Language.Rust.Data.Position | |
Show a => Show (Spanned a) Source # | |
Generic (Spanned a) Source # | |
NFData a => NFData (Spanned a) Source # | |
Defined in Language.Rust.Data.Position | |
Located (Spanned a) Source # | |
type Rep (Spanned a) Source # | |
Defined in Language.Rust.Data.Position type Rep (Spanned a) = D1 (MetaData "Spanned" "Language.Rust.Data.Position" "flp-0.1.0.0-DeMkA8gwwJbCOh6gqZDp9v" False) (C1 (MetaCons "Spanned" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 a) :*: S1 (MetaSel (Nothing :: Maybe Symbol) SourceUnpack SourceStrict DecidedStrict) (Rec0 Span))) |
class Located a where Source #
Describes nodes that can be located - their span can be extracted from them. In general, we
expect that for a value constructed as Con x y z
where Con
is an arbitrary constructor
(spanOf x <> spanOf y <> spanOf z) `subsetOf` spanOf (Con x y z) == True