Skip to content

Commit

Permalink
hopefully use jargon: alias, correlation name, qualified, with a bit
Browse files Browse the repository at this point in the history
  more consistency and correctness
add notes on the planned annotation type
added questions file to log these for later follow up
  • Loading branch information
Jake Wheat committed Sep 11, 2009
1 parent 696d6c2 commit 061599b
Show file tree
Hide file tree
Showing 8 changed files with 152 additions and 46 deletions.
40 changes: 20 additions & 20 deletions Ast.hs
Original file line number Diff line number Diff line change
Expand Up @@ -1624,8 +1624,8 @@ sem_Expression_Identifier i_ =
_lhsOmessages :: ([Message])
_lhsOactualValue :: Expression
_lhsOnodeType =
let (alias,iden) = splitIdentifier i_
in scopeLookupID _lhsIscope _lhsIsourcePos alias iden
let (correlationName,iden) = splitIdentifier i_
in scopeLookupID _lhsIscope _lhsIsourcePos correlationName iden
_lhsOliftedColumnName =
i_
_lhsOmessages =
Expand Down Expand Up @@ -2949,9 +2949,9 @@ sem_MTableRef Prelude.Nothing =
type T_MTableRef = Bool ->
Scope ->
MySourcePos ->
( MTableRef,([AliasedScope]),([String]),([Message]),Type)
( MTableRef,([QualifiedScope]),([String]),([Message]),Type)
data Inh_MTableRef = Inh_MTableRef {inLoop_Inh_MTableRef :: Bool,scope_Inh_MTableRef :: Scope,sourcePos_Inh_MTableRef :: MySourcePos}
data Syn_MTableRef = Syn_MTableRef {actualValue_Syn_MTableRef :: MTableRef,idens_Syn_MTableRef :: [AliasedScope],joinIdens_Syn_MTableRef :: [String],messages_Syn_MTableRef :: [Message],nodeType_Syn_MTableRef :: Type}
data Syn_MTableRef = Syn_MTableRef {actualValue_Syn_MTableRef :: MTableRef,idens_Syn_MTableRef :: [QualifiedScope],joinIdens_Syn_MTableRef :: [String],messages_Syn_MTableRef :: [Message],nodeType_Syn_MTableRef :: Type}
wrap_MTableRef :: T_MTableRef ->
Inh_MTableRef ->
Syn_MTableRef
Expand All @@ -2968,13 +2968,13 @@ sem_MTableRef_Just just_ =
(let _lhsOnodeType :: Type
_lhsOmessages :: ([Message])
_lhsOactualValue :: MTableRef
_lhsOidens :: ([AliasedScope])
_lhsOidens :: ([QualifiedScope])
_lhsOjoinIdens :: ([String])
_justOinLoop :: Bool
_justOscope :: Scope
_justOsourcePos :: MySourcePos
_justIactualValue :: TableRef
_justIidens :: ([AliasedScope])
_justIidens :: ([QualifiedScope])
_justIjoinIdens :: ([String])
_justImessages :: ([Message])
_justInodeType :: Type
Expand Down Expand Up @@ -3005,7 +3005,7 @@ sem_MTableRef_Nothing =
_lhsIscope
_lhsIsourcePos ->
(let _lhsOnodeType :: Type
_lhsOidens :: ([AliasedScope])
_lhsOidens :: ([QualifiedScope])
_lhsOjoinIdens :: ([String])
_lhsOmessages :: ([Message])
_lhsOactualValue :: MTableRef
Expand Down Expand Up @@ -3997,7 +3997,7 @@ sem_SelectExpression_Select selDistinct_ selSelectList_ selTref_ selWhere_ selGr
_selSelectListImessages :: ([Message])
_selSelectListInodeType :: Type
_selTrefIactualValue :: MTableRef
_selTrefIidens :: ([AliasedScope])
_selTrefIidens :: ([QualifiedScope])
_selTrefIjoinIdens :: ([String])
_selTrefImessages :: ([Message])
_selTrefInodeType :: Type
Expand Down Expand Up @@ -4267,9 +4267,9 @@ sem_SelectItemList_Cons hd_ tl_ =
_tlInodeType :: Type
_lhsOnodeType =
foldr consComposite _tlInodeType
(let (alias,iden) = splitIdentifier _hdIcolumnName
(let (correlationName,iden) = splitIdentifier _hdIcolumnName
in if iden == "*"
then scopeExpandStar _lhsIscope _lhsIsourcePos alias
then scopeExpandStar _lhsIscope _lhsIsourcePos correlationName
else [(iden, _hdInodeType)])
_lhsOmessages =
_hdImessages ++ _tlImessages
Expand Down Expand Up @@ -6320,9 +6320,9 @@ sem_TableRef (TrefFunAlias _fn _alias ) =
type T_TableRef = Bool ->
Scope ->
MySourcePos ->
( TableRef,([AliasedScope]),([String]),([Message]),Type)
( TableRef,([QualifiedScope]),([String]),([Message]),Type)
data Inh_TableRef = Inh_TableRef {inLoop_Inh_TableRef :: Bool,scope_Inh_TableRef :: Scope,sourcePos_Inh_TableRef :: MySourcePos}
data Syn_TableRef = Syn_TableRef {actualValue_Syn_TableRef :: TableRef,idens_Syn_TableRef :: [AliasedScope],joinIdens_Syn_TableRef :: [String],messages_Syn_TableRef :: [Message],nodeType_Syn_TableRef :: Type}
data Syn_TableRef = Syn_TableRef {actualValue_Syn_TableRef :: TableRef,idens_Syn_TableRef :: [QualifiedScope],joinIdens_Syn_TableRef :: [String],messages_Syn_TableRef :: [Message],nodeType_Syn_TableRef :: Type}
wrap_TableRef :: T_TableRef ->
Inh_TableRef ->
Syn_TableRef
Expand All @@ -6341,7 +6341,7 @@ sem_TableRef_JoinedTref tbl_ nat_ joinType_ tbl1_ onExpr_ =
_lhsIscope
_lhsIsourcePos ->
(let _lhsOnodeType :: Type
_lhsOidens :: ([AliasedScope])
_lhsOidens :: ([QualifiedScope])
_lhsOjoinIdens :: ([String])
_lhsOmessages :: ([Message])
_lhsOactualValue :: TableRef
Expand All @@ -6361,7 +6361,7 @@ sem_TableRef_JoinedTref tbl_ nat_ joinType_ tbl1_ onExpr_ =
_onExprOscope :: Scope
_onExprOsourcePos :: MySourcePos
_tblIactualValue :: TableRef
_tblIidens :: ([AliasedScope])
_tblIidens :: ([QualifiedScope])
_tblIjoinIdens :: ([String])
_tblImessages :: ([Message])
_tblInodeType :: Type
Expand All @@ -6372,7 +6372,7 @@ sem_TableRef_JoinedTref tbl_ nat_ joinType_ tbl1_ onExpr_ =
_joinTypeImessages :: ([Message])
_joinTypeInodeType :: Type
_tbl1IactualValue :: TableRef
_tbl1Iidens :: ([AliasedScope])
_tbl1Iidens :: ([QualifiedScope])
_tbl1IjoinIdens :: ([String])
_tbl1Imessages :: ([Message])
_tbl1InodeType :: Type
Expand Down Expand Up @@ -6455,7 +6455,7 @@ sem_TableRef_SubTref sel_ alias_ =
_lhsIscope
_lhsIsourcePos ->
(let _lhsOnodeType :: Type
_lhsOidens :: ([AliasedScope])
_lhsOidens :: ([QualifiedScope])
_lhsOjoinIdens :: ([String])
_lhsOmessages :: ([Message])
_lhsOactualValue :: TableRef
Expand Down Expand Up @@ -6494,7 +6494,7 @@ sem_TableRef_Tref tbl_ =
_lhsIsourcePos ->
(let _lhsOnodeType :: Type
_lhsOjoinIdens :: ([String])
_lhsOidens :: ([AliasedScope])
_lhsOidens :: ([QualifiedScope])
_lhsOmessages :: ([Message])
_lhsOactualValue :: TableRef
_lhsOnodeType =
Expand All @@ -6519,7 +6519,7 @@ sem_TableRef_TrefAlias tbl_ alias_ =
_lhsIsourcePos ->
(let _lhsOnodeType :: Type
_lhsOjoinIdens :: ([String])
_lhsOidens :: ([AliasedScope])
_lhsOidens :: ([QualifiedScope])
_lhsOmessages :: ([Message])
_lhsOactualValue :: TableRef
_lhsOnodeType =
Expand All @@ -6543,7 +6543,7 @@ sem_TableRef_TrefFun fn_ =
_lhsIsourcePos ->
(let _lhsOnodeType :: Type
_lhsOjoinIdens :: ([String])
_lhsOidens :: ([AliasedScope])
_lhsOidens :: ([QualifiedScope])
_lhsOmessages :: ([Message])
_lhsOactualValue :: TableRef
_fnOinLoop :: Bool
Expand Down Expand Up @@ -6583,7 +6583,7 @@ sem_TableRef_TrefFunAlias fn_ alias_ =
_lhsIsourcePos ->
(let _lhsOnodeType :: Type
_lhsOjoinIdens :: ([String])
_lhsOidens :: ([AliasedScope])
_lhsOidens :: ([QualifiedScope])
_lhsOmessages :: ([Message])
_lhsOactualValue :: TableRef
_fnOinLoop :: Bool
Expand Down
2 changes: 1 addition & 1 deletion AstCheckTests.lhs
Original file line number Diff line number Diff line change
Expand Up @@ -352,7 +352,7 @@ todo:
> [SetOfType $ UnnamedCompositeType [("adsrc", ScalarType "text")]]

> ,p "select pg_attrdef.adsrc from pg_attrdef a;"
> [TypeError ("",1,1) (UnrecognisedAlias "pg_attrdef")]
> [TypeError ("",1,1) (UnrecognisedCorrelationName "pg_attrdef")]

> ,p "select a from (select 2 as b, 1 as a) a\n\
> \natural inner join (select 4.5 as d, 1 as a) b;"
Expand Down
2 changes: 1 addition & 1 deletion README
Original file line number Diff line number Diff line change
Expand Up @@ -61,7 +61,7 @@ jakewheatmail@gmail.com
== Parsing

Partially supports:
select statements (selectlists (*, qualified, aliased, expressions)
select statements (selectlists (*, qualified, aliased/correlation names, expressions)
distinct, basic window functions,
from (with explicit joins - natural, inner, cross, left, right,
full outer, on and using), aliases, from functions
Expand Down
33 changes: 17 additions & 16 deletions Scope.lhs
Original file line number Diff line number Diff line change
Expand Up @@ -25,19 +25,20 @@ extra definitions from an accessible database.
> --this should be done better:
> ,scopeAllFns :: [FunctionPrototype]
> ,scopeAttrDefs :: [CompositeDef]
> ,scopeIdentifierTypes :: [AliasedScope]
> ,scopeIdentifierTypes :: [QualifiedScope]
> ,scopeJoinIdentifiers :: [String]}
> deriving (Eq,Show)

= Attribute identifier scoping

The way this scoping works is we have a list of prefixes/namespaces,
which is generally the table/view name, or the alias given to it, and
then a list of unaliased identifiers and their types. When we look
something up, if it has an alias we just look in that list, if it is
then a list of identifiers (with no dots) and their types. When we
look up the type of an identifier, if it has an correlation name we
try to match that against a table name or alias in that list, if it is
not present or not unique then throw an error. Similarly with no
alias, we look at all the lists, if the id is not present or not
unique then throw an error.
correlation name, we look at all the lists, if the id is not present
or not unique then throw an error.

scopeIdentifierTypes is for expanding *. If we want to access the
common attributes from one of the tables in a using or natural join,
Expand All @@ -47,19 +48,19 @@ once, so keep a separate list of these fields used just for expanding
the star. The other twist is that these common fields appear first in
the resultant field list.

> type AliasedScope = (String, [(String,Type)])
> type QualifiedScope = (String, [(String,Type)])

> emptyScope :: Scope
> emptyScope = Scope [] [] [] [] [] [] [] [] [] [] [] []

> scopeReplaceIds :: Scope -> [AliasedScope] -> [String] -> Scope
> scopeReplaceIds :: Scope -> [QualifiedScope] -> [String] -> Scope
> scopeReplaceIds scope ids commonJoinFields =
> scope { scopeIdentifierTypes = ids
> ,scopeJoinIdentifiers = commonJoinFields }

> scopeLookupID :: Scope -> MySourcePos -> String -> String -> Type
> scopeLookupID scope sp alias iden =
> if alias == ""
> scopeLookupID scope sp correlationName iden =
> if correlationName == ""
> then let types = concatMap (filter (\ (s, _) -> s == iden))
> (map snd $ scopeIdentifierTypes scope)
> in case length types of
Expand All @@ -69,22 +70,22 @@ the resultant field list.
> if iden `elem` scopeJoinIdentifiers scope
> then (snd . head) types
> else TypeError sp (AmbiguousIdentifier iden)
> else case lookup alias (scopeIdentifierTypes scope) of
> Nothing -> TypeError sp $ UnrecognisedAlias alias
> else case lookup correlationName (scopeIdentifierTypes scope) of
> Nothing -> TypeError sp $ UnrecognisedCorrelationName correlationName
> Just s -> case lookup iden s of
> Nothing -> TypeError sp $ UnrecognisedIdentifier $ alias ++ "." ++ iden
> Nothing -> TypeError sp $ UnrecognisedIdentifier $ correlationName ++ "." ++ iden
> Just t -> t

> scopeExpandStar :: Scope -> MySourcePos -> String -> [(String,Type)]
> scopeExpandStar scope sp alias =
> if alias == ""
> scopeExpandStar scope sp correlationName =
> if correlationName == ""
> then let allFields = concatMap snd $ scopeIdentifierTypes scope
> (commonFields,uncommonFields) =
> partition (\(a,_) -> a `elem` scopeJoinIdentifiers scope) allFields
> in nub commonFields ++ uncommonFields
> else
> case lookup alias (scopeIdentifierTypes scope) of
> Nothing -> [("", TypeError sp $ UnrecognisedAlias alias)]
> case lookup correlationName (scopeIdentifierTypes scope) of
> Nothing -> [("", TypeError sp $ UnrecognisedCorrelationName correlationName)]
> Just s -> s


Expand Down
42 changes: 41 additions & 1 deletion TODO
Original file line number Diff line number Diff line change
@@ -1,3 +1,43 @@
Annotation planning
add an annotation field to most nodes in the ast
something like
data Annotation = NonAnnotation
| SourcePosAnnotation SourcePos
| CheckedAnnotation SourcePos Type [Messages]

alter the parser to add sourcepositions to these nodes - assume that
one source position per node will be enough for now (not
necessarily a good assumption with weird sql syntax), and see if
this gives us enough for good error messages, etc..

question:
if a node has no source position e.g. the all in select all or select
distinct may correspond to a token or may be synthesized as the
default if neither all or distinct is present. Should this have the
source position of where the token would have appeared, should it
inherit it from its parent, should there be a separate ctor to
represent this?

The way the type checking will then work is that instead of producing
some attribute values it will produce a transformed ast tree with
the type and message fields filled in. Then supply some utility
functions to e.g. extract all the messages, extract all the type
errors, extract the top level types, etc. Use some sort of tree
walker to implement this utils

The way types and type errors will work is that instead of / in
addition to the types being passed in attributes, they'll be saved
in the transformed tree. Type errors won't percolate up to the top
level, but sit with the node that is in error. Any parent nodes
which need this type to calculate their own type, will use a
separate error to say type unknown. If they can calculate their
type without depending on a type erroring child node, then they do
that, so e.g. typing a set of statements with create functions
and views which use those functions: if the statements inside the
functions have type errors, we can still find the types of the
views, assuming that the function params and return type properly,
and are correct.


= Current TODO list

Expand All @@ -14,7 +54,7 @@ creates - just enough to fill in the scope so references to these type
support for domains implicitly casting to base types in function
lookup, result set resolution
simple typing of aggregate args and return types
Pretty printer for types
Pretty printer for Type
aliases in selects from functions - when the function returns a setof
single type instead of composite, then the single return attribute
takes the alias name as it's attribute name e.g. select x from
Expand Down
12 changes: 6 additions & 6 deletions TypeChecking.ag
Original file line number Diff line number Diff line change
Expand Up @@ -226,8 +226,8 @@ pull id types out of scope for identifiers

SEM Expression
| Identifier lhs.nodeType =
let (alias,iden) = splitIdentifier @i
in scopeLookupID @lhs.scope @lhs.sourcePos alias iden
let (correlationName,iden) = splitIdentifier @i
in scopeLookupID @lhs.scope @lhs.sourcePos correlationName iden

{
-- i think this should be alright, an identifier referenced in an
Expand Down Expand Up @@ -366,9 +366,9 @@ SEM SelectItem
SEM SelectItemList
| Cons lhs.nodeType =
foldr consComposite @tl.nodeType
(let (alias,iden) = splitIdentifier @hd.columnName
(let (correlationName,iden) = splitIdentifier @hd.columnName
in if iden == "*"
then scopeExpandStar @lhs.scope @lhs.sourcePos alias
then scopeExpandStar @lhs.scope @lhs.sourcePos correlationName
else [(iden, @hd.nodeType)])
| Nil lhs.nodeType = UnnamedCompositeType []

Expand All @@ -392,13 +392,13 @@ them into the selectlist and where parts)
ATTR TableRef
[
|
| idens : {[AliasedScope]} joinIdens : {[String]}
| idens : {[QualifiedScope]} joinIdens : {[String]}
]

ATTR MTableRef
[
|
| idens : {[AliasedScope]} joinIdens : {[String]}
| idens : {[QualifiedScope]} joinIdens : {[String]}
]


Expand Down
2 changes: 1 addition & 1 deletion TypeType.lhs
Original file line number Diff line number Diff line change
Expand Up @@ -111,7 +111,7 @@ later on down the line.
> | NoRowsGivenForValues
> | UnrecognisedIdentifier String
> | UnrecognisedRelation String
> | UnrecognisedAlias String
> | UnrecognisedCorrelationName String
> | AmbiguousIdentifier String
> | ContextError String
> | MissingJoinAttribute
Expand Down
Loading

0 comments on commit 061599b

Please sign in to comment.