some utilities which are used by catalog builder and by catalog
internals
> {-# LANGUAGE OverloadedStrings #-}
> module Database.HsSqlPpp.Internals.Catalog.CatalogUtils
> (catLookupType, getCatName) where
> import Database.HsSqlPpp.Internals.Catalog.CatalogTypes
>
>
>
>
>
> import qualified Data.Map as M
> import qualified Data.Set as S
> import Database.HsSqlPpp.Internals.TypesInternal
>
>
>
>
>
>
names to refer to the pseudo types. This is very postgresql
specific. Some of these should be deleted since hssqlppp has nothing
to do with them. Some of them will become postgresql dialect specific
and not appear here, and some we will repurpose to implement features
for non-postgresql dialects as well.
> pseudoTypes :: M.Map CatName Type
> pseudoTypes = M.fromList
> [("any",Pseudo Any)
> ,("anyarray",Pseudo AnyArray)
> ,("anyelement",Pseudo AnyElement)
> ,("anyenum",Pseudo AnyEnum)
> ,("anyrange",Pseudo AnyRange)
> ,("anynonarray",Pseudo AnyNonArray)
>
> ,("record",Pseudo (Record Nothing))
>
>
>
> ,("void",Pseudo Void)
>
> ,("_record",ArrayType $ Pseudo (Record Nothing))
>
>
>
>
> ]
>
>
> catLookupType :: Catalog -> [NameComponent] -> Either [TypeError] Type
> catLookupType cat ncs =
> case getCatName ncs of
>
> cn | Just p <- M.lookup cn pseudoTypes -> Right p
>
> | S.member cn (catScalarTypeNames cat) -> Right $ ScalarType cn
> | M.member cn (catDomainTypes cat) -> Right $ DomainType cn
> | M.member cn (catCompositeTypes cat) -> Right $ NamedCompositeType cn
> | Just t <- M.lookup cn (catArrayTypes cat) -> Right $ ArrayType $ ScalarType t
> | otherwise -> Left [UnknownTypeName cn]
> getCatName :: [NameComponent] -> CatName
> getCatName [] = error "empty name component in catalog code"
> getCatName [x] = ncStrT x
> getCatName (_:xs) = getCatName xs