Safe Haskell | None |
---|---|
Language | Haskell2010 |
Contains the annotation data types and a few auxiliary functions.
Synopsis
- data Annotation = Annotation {
- anSrc :: Maybe SourcePosition
- anType :: Maybe TypeExtra
- anErrs :: [TypeError]
- anImplicitCast :: Maybe TypeExtra
- anCatUpd :: [CatalogUpdate]
- type SourcePosition = (FilePath, Int, Int)
- getAnnotation :: Data a => a -> Annotation
- updateAnnotation :: Data a => (Annotation -> Annotation) -> a -> a
- emptyAnnotation :: Annotation
Annotation data types
data Annotation Source #
Annotation type - one of these is attached to most of the data types used in the ast. the fields in order are:
Annotation | |
|
Instances
Eq Annotation Source # | |
Defined in Database.HsSqlPpp.Internals.AstInternal (==) :: Annotation -> Annotation -> Bool # (/=) :: Annotation -> Annotation -> Bool # | |
Data Annotation Source # | |
Defined in Database.HsSqlPpp.Internals.AstInternal gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Annotation -> c Annotation # gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Annotation # toConstr :: Annotation -> Constr # dataTypeOf :: Annotation -> DataType # dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Annotation) # dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Annotation) # gmapT :: (forall b. Data b => b -> b) -> Annotation -> Annotation # gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Annotation -> r # gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Annotation -> r # gmapQ :: (forall d. Data d => d -> u) -> Annotation -> [u] # gmapQi :: Int -> (forall d. Data d => d -> u) -> Annotation -> u # gmapM :: Monad m => (forall d. Data d => d -> m d) -> Annotation -> m Annotation # gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Annotation -> m Annotation # gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Annotation -> m Annotation # | |
Show Annotation Source # | |
Defined in Database.HsSqlPpp.Internals.AstInternal showsPrec :: Int -> Annotation -> ShowS # show :: Annotation -> String # showList :: [Annotation] -> ShowS # |
type SourcePosition = (FilePath, Int, Int) Source #
Represents a source file position, usually set by the parser.
getAnnotation :: Data a => a -> Annotation Source #
get the annotation for the root element of the tree passed
updateAnnotation :: Data a => (Annotation -> Annotation) -> a -> a Source #
Update the first annotation in a tree using the function supplied
emptyAnnotation :: Annotation Source #
An annotation value with no information.