hssqlppp-0.6.2: SQL parser and type checker

Safe HaskellNone
LanguageHaskell2010

Database.HsSqlPpp.Catalog

Contents

Description

This module contains the database catalog data types and helper functions.

The catalog data type holds the catalog information needed to type check sql code, and a catalog value is produced after typechecking sql which represents the catalog that would be produced (e.g. for sql containing ddl)

You can create a catalog using the CatalogUpdate type, and there is example and util in the repo which reads a catalog from an existing database in postgres.

Synopsis

Data types

data Catalog Source #

The main datatype, this holds the catalog and context information to type check against.

Instances
Eq Catalog Source # 
Instance details

Defined in Database.HsSqlPpp.Internals.Catalog.CatalogTypes

Methods

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

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

Data Catalog Source # 
Instance details

Defined in Database.HsSqlPpp.Internals.Catalog.CatalogTypes

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Catalog -> c Catalog #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Catalog #

toConstr :: Catalog -> Constr #

dataTypeOf :: Catalog -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Catalog) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Catalog) #

gmapT :: (forall b. Data b => b -> b) -> Catalog -> Catalog #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Catalog -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Catalog -> r #

gmapQ :: (forall d. Data d => d -> u) -> Catalog -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Catalog -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Catalog -> m Catalog #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Catalog -> m Catalog #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Catalog -> m Catalog #

Show Catalog Source # 
Instance details

Defined in Database.HsSqlPpp.Internals.Catalog.CatalogTypes

Updates

data CatalogUpdate Source #

Constructors

CatCreateSchema CatName

register a schema with the given name

CatCreateScalarType CatName

register a base scalar type with the given name

CatCreateDomainType CatName CatName

register a domain type with name and base type

CatCreateArrayType CatName CatName

register an array type with name and base type

CatCreatePrefixOp CatName CatName CatName

register a prefix op, opname, param type, return type

CatCreatePostfixOp CatName CatName CatName

register a postfix op, opname, param type, return type

CatCreateBinaryOp CatName CatName CatName CatName

register a binary op, opname, the two param types, return type

CatCreateFunction CatName [CatName] Bool CatName

register a function: name, param types, retsetof, return type

CatCreateVariadicFunction CatName [CatName] Bool CatName

register a variadic function: name, param types, retsetof, return type the last parameter will be wrapped in an array type

CatCreateSpecialOp CatName [CatName] Bool CatName

special ops include between, substring, position, basically all operators/functions which use mixfix or extra syntax (not including non scalar functions like aggregates)

CatCreateAggregate CatName [CatName] CatName

register a aggregate: name, param types, return type

CatCreateTable (CatName, CatName) [(CatName, CatNameExtra)]

register a table only: name, (colname,typename) pairs

CatCreateCast CatName CatName CastContext

register a cast in the catalog

CatCreateTypeCategoryEntry CatName (Text, Bool)

register a type category for a type (used in the implicit cast resolution)

Instances
Eq CatalogUpdate Source # 
Instance details

Defined in Database.HsSqlPpp.Internals.Catalog.CatalogTypes

Data CatalogUpdate Source # 
Instance details

Defined in Database.HsSqlPpp.Internals.Catalog.CatalogTypes

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CatalogUpdate -> c CatalogUpdate #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CatalogUpdate #

toConstr :: CatalogUpdate -> Constr #

dataTypeOf :: CatalogUpdate -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CatalogUpdate) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CatalogUpdate) #

gmapT :: (forall b. Data b => b -> b) -> CatalogUpdate -> CatalogUpdate #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CatalogUpdate -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CatalogUpdate -> r #

gmapQ :: (forall d. Data d => d -> u) -> CatalogUpdate -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CatalogUpdate -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CatalogUpdate -> m CatalogUpdate #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CatalogUpdate -> m CatalogUpdate #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CatalogUpdate -> m CatalogUpdate #

Ord CatalogUpdate Source # 
Instance details

Defined in Database.HsSqlPpp.Internals.Catalog.CatalogTypes

Show CatalogUpdate Source # 
Instance details

Defined in Database.HsSqlPpp.Internals.Catalog.CatalogTypes

bits and pieces

data CastContext Source #

Use to note what the flavour of a cast is, i.e. if/when it can be used implicitly.

Instances
Eq CastContext Source # 
Instance details

Defined in Database.HsSqlPpp.Internals.Catalog.CatalogTypes

Data CastContext Source # 
Instance details

Defined in Database.HsSqlPpp.Internals.Catalog.CatalogTypes

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CastContext -> c CastContext #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CastContext #

toConstr :: CastContext -> Constr #

dataTypeOf :: CastContext -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CastContext) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CastContext) #

gmapT :: (forall b. Data b => b -> b) -> CastContext -> CastContext #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CastContext -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CastContext -> r #

gmapQ :: (forall d. Data d => d -> u) -> CastContext -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CastContext -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CastContext -> m CastContext #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CastContext -> m CastContext #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CastContext -> m CastContext #

Ord CastContext Source # 
Instance details

Defined in Database.HsSqlPpp.Internals.Catalog.CatalogTypes

Show CastContext Source # 
Instance details

Defined in Database.HsSqlPpp.Internals.Catalog.CatalogTypes

data CompositeFlavour Source #

Instances
Eq CompositeFlavour Source # 
Instance details

Defined in Database.HsSqlPpp.Internals.Catalog.CatalogTypes

Data CompositeFlavour Source # 
Instance details

Defined in Database.HsSqlPpp.Internals.Catalog.CatalogTypes

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CompositeFlavour -> c CompositeFlavour #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CompositeFlavour #

toConstr :: CompositeFlavour -> Constr #

dataTypeOf :: CompositeFlavour -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CompositeFlavour) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CompositeFlavour) #

gmapT :: (forall b. Data b => b -> b) -> CompositeFlavour -> CompositeFlavour #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CompositeFlavour -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CompositeFlavour -> r #

gmapQ :: (forall d. Data d => d -> u) -> CompositeFlavour -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CompositeFlavour -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CompositeFlavour -> m CompositeFlavour #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CompositeFlavour -> m CompositeFlavour #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CompositeFlavour -> m CompositeFlavour #

Ord CompositeFlavour Source # 
Instance details

Defined in Database.HsSqlPpp.Internals.Catalog.CatalogTypes

Show CompositeFlavour Source # 
Instance details

Defined in Database.HsSqlPpp.Internals.Catalog.CatalogTypes

type CatName = Text Source #

represents the name of something in the catalog, when schema support is added then this will change to (String,String)

data CatNameExtra Source #

type name and precision and nullability

Instances
Eq CatNameExtra Source # 
Instance details

Defined in Database.HsSqlPpp.Internals.Catalog.CatalogTypes

Data CatNameExtra Source # 
Instance details

Defined in Database.HsSqlPpp.Internals.Catalog.CatalogTypes

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> CatNameExtra -> c CatNameExtra #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c CatNameExtra #

toConstr :: CatNameExtra -> Constr #

dataTypeOf :: CatNameExtra -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c CatNameExtra) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c CatNameExtra) #

gmapT :: (forall b. Data b => b -> b) -> CatNameExtra -> CatNameExtra #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> CatNameExtra -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> CatNameExtra -> r #

gmapQ :: (forall d. Data d => d -> u) -> CatNameExtra -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> CatNameExtra -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> CatNameExtra -> m CatNameExtra #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> CatNameExtra -> m CatNameExtra #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> CatNameExtra -> m CatNameExtra #

Ord CatNameExtra Source # 
Instance details

Defined in Database.HsSqlPpp.Internals.Catalog.CatalogTypes

Show CatNameExtra Source # 
Instance details

Defined in Database.HsSqlPpp.Internals.Catalog.CatalogTypes

Functions

updateCatalog :: [CatalogUpdate] -> Catalog -> Either [TypeError] Catalog Source #

Applies a list of CatalogUpdates to an Catalog value to produce a new Catalog value. TODO: there will be a split between the individual low level updates which just update one row in the catalog type, and the high level updates which correspond to ddl (e.g. create type will also add the array type, create table will add a table, supply the private columns automatically, and add the composite type) highlevel not implemented yet. You must use the correct case and the canonical names for identifiers/types

testing support

data Environment Source #

Represent an environment using an abstracted version of the syntax which produced the environment. This structure has all the catalog queries resolved. No attempt is made to combine environment parts from different sources, they are just stacked together, the logic for working with combined environments is in the query functions below

Instances
Eq Environment Source # 
Instance details

Defined in Database.HsSqlPpp.Internals.TypeChecking.Environment

Data Environment Source # 
Instance details

Defined in Database.HsSqlPpp.Internals.TypeChecking.Environment

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Environment -> c Environment #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c Environment #

toConstr :: Environment -> Constr #

dataTypeOf :: Environment -> DataType #

dataCast1 :: Typeable t => (forall d. Data d => c (t d)) -> Maybe (c Environment) #

dataCast2 :: Typeable t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Environment) #

gmapT :: (forall b. Data b => b -> b) -> Environment -> Environment #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Environment -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Environment -> r #

gmapQ :: (forall d. Data d => d -> u) -> Environment -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Environment -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Environment -> m Environment #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Environment -> m Environment #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Environment -> m Environment #

Show Environment Source # 
Instance details

Defined in Database.HsSqlPpp.Internals.TypeChecking.Environment

brokeEnvironment :: Environment Source #

represents type check failure upstream, don't produce additional type check errors