Type identifiers and anonymous types
Basic type identified by name
These can be quoted or unquoted, and with or without schema
unknown type: this is used for the types of literals in a kind of poor
mans type inference, modelled on postgresql's behaviour. Dialects can
choose not to use this approach and give a literal a type based only
on its syntax (and thus the dialect would never use the unknown
type. (The direct unknown typing isn't quite implemented yet).
any types
these are used to implement a kind of poor man's polymorphism. based
on the any types in postgresql. These are used for polymorphic
udfs. This is separate to overloading functions.
anonymous composite type
this represents a tuple of types, all, some or none of which can have
field names. This is used for composite types which are created on the
fly and don't have a name in the catalog or environment. Maybe this
should be changed so they are given a temporary name to reduce the
special cases
tref type
this is an internal type used by the typechecker (todo: can this be
hidden?) Maybe could add optional correlation names to the field names
in anonymous composite type and reuse that?
setof?
record?
void?
typeextra
ugly way to add nullability and precision to a type. This should get a
big rethink
step 1 todo:
combine composite and anonymous composite types
combine scalartype, domaintype, enum, named composite type
get rid of explicit array types and figure out a better way to handle
them
Split the errors into another module, and in the public api
The errors should contain not contain 'Type's.
figure out a better way of handling nullability, precision, scale than
the typeextra
>
>
> module Database.HsSqlPpp.Internals.TypesInternal where
>
> import Data.Data
>
>
> import Data.Text (Text)
>
>
>
>
>
>
>
where should precision and nullability go?
TODO:
rename UnknownType to ScalarType "!unknown" ? or something else?
do we need separate entries for domain and enums?
think of a better way to implement array types - get rid of the
special casing which is based on a postgresql implementation detail
get rid of pseudo types, maybe use ScalarType or SpecialType String
which is dialect specific?
Maybe there should be a concept of a typeid, and a typedescription?
So the typeid is used everywhere and is just a string or something,
and the typedescription is got from the catalog/environment when
needed in the typechecking?
>
>
> data Type =
>
> ScalarType Text
>
>
>
> | DomainType Text
>
> | EnumType Text
>
>
>
>
>
> | UnknownType
>
>
>
> | ArrayType Type
>
>
> | NamedCompositeType Text
>
> | CompositeType [(Text,TypeExtra)]
>
>
> | TrefType [((Text,Text),TypeExtra)]
>
> | AnonymousCompositeType [Type]
>
>
>
>
>
> | Pseudo PseudoType
> deriving (Eq,Show,Ord,Typeable,Data)
>
>
>
>
> data TypeExtra = TypeExtra {teType :: Type
> ,tePrecision :: Maybe Int
> ,teScale :: Maybe Int
> ,teNullable :: Bool}
> deriving (Eq,Ord,Show,Typeable,Data)
> mkTypeExtra :: Type -> TypeExtra
> mkTypeExtra t = TypeExtra t Nothing Nothing True
> mkTypeExtraNN :: Type -> TypeExtra
> mkTypeExtraNN t = TypeExtra t Nothing Nothing False
> mkNullable:: TypeExtra -> TypeExtra
> mkNullable te = te{teNullable=True}
>
>
>
> data PseudoType =
>
> SetOfType Type
>
>
>
>
> | AnyElement
>
> | AnyArray
>
> | AnyEnum
>
> | AnyNonArray
> | AnyRange
>
>
> | Any
>
>
>
>
> | Record (Maybe Type)
>
>
>
>
>
>
>
>
>
> | Void
>
>
>
>
> deriving (Eq,Show,Ord,Typeable,Data)
TODO idea
>
The possible type errors. This is a bit unorganised, at some point if
better error messages are wanted, then a lot more information could be
added.
> data TypeError =
type conversion errors
> | } NoMatchingOperator Text [Type]
> | AmbiguousOperator Text [Type]
> | TypelessEmptyArray
> | IncompatibleTypeSet [Type]
> | IncompatibleTypes Type Type
> | WrongNumberOfColumns
> | WrongTypes Type [Type]
> | IncompatibleUnionTypes Type Type
old catalog type errors: to be replaced when the catalog code is
gutted and rewritten
> | TypeAlreadyExists Type
> | SchemaAlreadyExists Text
> | BadCatalogUpdate Text
> | UnrecognisedRelation (Text,Text)
> | DomainDefNotFound Type
> | TypeNotKnown Type
> | UnknownTypeName Text
> | UnrecognisedIdentifier Text
> | UnrecognisedCorrelationName Text
> | SchemadColumnName Text
> | DbSchemadColumnName Text
> | BadStarExpand
> | InternalError String
> | AmbiguousIdentifier Text
> | OdbcFuncBadContent
> | DuplicateColumnName Text
> | TooManyColumnsInInsert
> deriving (Eq,Show,Ord,Typeable,Data)
>