ivory-0.1.0.8: Safe embedded C programming.

Safe HaskellSafe
LanguageHaskell2010

Ivory.Language.Syntax.Concrete.Location

Synopsis

Documentation

class HasLocation a where Source #

Minimal complete definition

getLoc, stripLoc

Methods

getLoc :: a -> SrcLoc Source #

stripLoc :: a -> a Source #

Instances
HasLocation SrcLoc Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

HasLocation BitField Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.ParseAST

HasLocation Constr Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.ParseAST

HasLocation BitTy Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.ParseAST

HasLocation BitDataDef Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.ParseAST

HasLocation Field Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.ParseAST

HasLocation StructDef Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.ParseAST

HasLocation Stmt Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.ParseAST

HasLocation AllocRef Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.ParseAST

HasLocation StructInit Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.ParseAST

HasLocation Exp Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.ParseAST

HasLocation Type Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.ParseAST

HasLocation PrePost Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.ParseAST

HasLocation IncludeProc Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.ParseAST

HasLocation ProcDef Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.ParseAST

HasLocation TypeDef Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.ParseAST

HasLocation ConstDef Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.ParseAST

HasLocation Extern Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.ParseAST

HasLocation IncludeDef Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.ParseAST

HasLocation AreaImportDef Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.ParseAST

HasLocation AreaDef Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.ParseAST

HasLocation GlobalSym Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.ParseAST

HasLocation a => HasLocation [a] Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

Methods

getLoc :: [a] -> SrcLoc Source #

stripLoc :: [a] -> [a] Source #

HasLocation a => HasLocation (Maybe a) Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

Methods

getLoc :: Maybe a -> SrcLoc Source #

stripLoc :: Maybe a -> Maybe a Source #

HasLocation (Located a) Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

(HasLocation a, HasLocation b) => HasLocation (a, b) Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

Methods

getLoc :: (a, b) -> SrcLoc Source #

stripLoc :: (a, b) -> (a, b) Source #

data Located a Source #

Things that carry a range in the source syntax.

Constructors

Located 

Fields

Instances
Functor Located Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

Methods

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

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

Foldable Located Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

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 Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

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) #

Eq a => Eq (Located a) Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

Methods

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

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

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

Defined in Ivory.Language.Syntax.Concrete.Location

Methods

compare :: Located a -> Located a -> Ordering #

(<) :: Located a -> Located a -> Bool #

(<=) :: Located a -> Located a -> Bool #

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

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

max :: Located a -> Located a -> Located a #

min :: Located a -> Located a -> Located a #

Read a => Read (Located a) Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

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

Defined in Ivory.Language.Syntax.Concrete.Location

Methods

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

show :: Located a -> String #

showList :: [Located a] -> ShowS #

HasLocation (Located a) Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

noLoc :: a -> Located a Source #

Attach no location information to a value.

at :: HasLocation loc => a -> loc -> Located a Source #

Attach location information to a value.

atBin :: (HasLocation loc0, HasLocation loc1) => a -> loc0 -> loc1 -> Located a Source #

at helper for binary operators.

atList :: a -> [SrcLoc] -> Located a Source #

at helper for list args.

unLoc :: Located a -> a Source #

Strip off location information.

extendLoc :: SrcLoc -> Located a -> Located a Source #

Extend the range of a located thing.

type Source = Maybe String Source #

Source locations.

data SrcLoc Source #

A range in the program source.

Constructors

NoLoc 
SrcLoc !Range Source 
Instances
Eq SrcLoc Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

Methods

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

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

Ord SrcLoc Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

Read SrcLoc Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

Show SrcLoc Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

Semigroup SrcLoc Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

Monoid SrcLoc Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

Lift SrcLoc # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

lift :: SrcLoc -> Q Exp #

Pretty SrcLoc Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

Methods

pretty :: SrcLoc -> Doc Source #

HasLocation SrcLoc Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

srcLoclinePragma :: SrcLoc -> Maybe (Int, String) Source #

Get info to build a line pragma from a SrcLoc. Returns a value only if there is a valid range. Returns the starting line number.

srcStart :: SrcLoc -> Position Source #

Starting Position of a SrcLoc.

srcEnd :: SrcLoc -> Position Source #

Ending Position of a SrcLoc.

data Range Source #

The region between to source positions.

Constructors

Range 
Instances
Eq Range Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

Methods

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

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

Ord Range Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

Methods

compare :: Range -> Range -> Ordering #

(<) :: Range -> Range -> Bool #

(<=) :: Range -> Range -> Bool #

(>) :: Range -> Range -> Bool #

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

max :: Range -> Range -> Range #

min :: Range -> Range -> Range #

Read Range Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

Show Range Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

Methods

showsPrec :: Int -> Range -> ShowS #

show :: Range -> String #

showList :: [Range] -> ShowS #

Semigroup Range Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

Methods

(<>) :: Range -> Range -> Range #

sconcat :: NonEmpty Range -> Range #

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

Monoid Range Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

Methods

mempty :: Range #

mappend :: Range -> Range -> Range #

mconcat :: [Range] -> Range #

Lift Range # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

lift :: Range -> Q Exp #

Pretty Range Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

Methods

pretty :: Range -> Doc Source #

data Position Source #

Position information within a source.

Constructors

Position 

Fields

Instances
Eq Position Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

Ord Position Source #

This only compares offset, assuming that the positions come from the same source.

Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

Read Position Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

Show Position Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

Lift Position # 
Instance details

Defined in Ivory.Language.Syntax.AST

Methods

lift :: Position -> Q Exp #

Pretty Position Source # 
Instance details

Defined in Ivory.Language.Syntax.Concrete.Location

Methods

pretty :: Position -> Doc Source #

zeroPosition :: Position Source #

Starting position.

smallerOf :: Position -> Position -> Position Source #

Return smaller of the two positions, taking care to not allow the zero position to dominate.

largerOf :: Position -> Position -> Position Source #

Return the larger of the two positions.

movePos :: Position -> Char -> Position Source #

Given a character, increment a position.

movesPos :: Position -> String -> Position Source #

Move many characters at once.