For extra utility functions to help with asts
> module Database.HsSqlPpp.Internals.TypeChecking.Utils
> (addExplicitCasts
> ,canonicalizeTypeNames) where
> import Data.Data
> import Database.HsSqlPpp.Internals.AstInternal
> import Data.Generics.Uniplate.Data
> import Database.HsSqlPpp.Internals.AstAnnotation
> import Database.HsSqlPpp.Internals.TypeType
> import Control.Monad
>
>
>
>
> addExplicitCasts :: Data a => a -> a
> addExplicitCasts =
> refix . tr . canonicalizeTypeNames
> where
> tr = transformBi $ \x -> case x of
> FunCall a f as | Just p <- getProtoATys a
> , Just ats <- getTys as
> , p /= ats
> -> FunCall a f $ zipWith3 addCastIfNeeded p ats as
> Case a cs els | (Just f) <- doCase a cs els -> f
> CaseSimple a v cs els | (Just f) <- doCaseSimple a v cs els -> f
> i@(NumberLit a _) | Just t <- infType a -> castToT t i
> i@(StringLit a _) | Just t <- infType a -> castToT t i
> x1 -> x1
>
>
> castToT t e = Cast ea {atype = Just t,infType = Just t} e $ typeName 1 t
> getProtoATys :: Annotation -> Maybe [Type]
> getProtoATys a = let p = fnProt a
> in flip fmap p $ \(_,t,_,_) -> t
> getTys :: [ScalarExpr] -> Maybe [Type]
> getTys = mapM $ atype . getAnnotation
> addCastIfNeeded :: Type -> Type -> ScalarExpr -> ScalarExpr
> addCastIfNeeded nt ot e =
> if ot == nt
> then e
> else Cast ea e $ typeName 2 nt
>
>
>
>
>
>
> refix = transformBi $ \x -> case x of
> Cast ca (Cast _ l t) t1 | isLiteral l
> , Just lt <- infType $ getAnnotation l
> , t == typeName 3 lt
> -> Cast ca l t1
> x1 -> x1
> isLiteral (NumberLit _ _) = True
> isLiteral (StringLit _ _) = True
> isLiteral _ = False
> typeName :: Int -> Type -> TypeName
> typeName _ (ScalarType t) = SimpleTypeName ea t
> typeName i e = error $ "don't know how to convert " ++ show e ++ " to typename " ++ show i
> ea :: Annotation
> ea = emptyAnnotation
> doCase :: Annotation -> [([ScalarExpr],ScalarExpr)] -> Maybe ScalarExpr -> Maybe ScalarExpr
> doCase a whths els = do
> (whths',els') <- doCaseStuff a whths els
> return $ Case a whths' els'
> doCaseSimple :: Annotation -> ScalarExpr -> [([ScalarExpr],ScalarExpr)] -> Maybe ScalarExpr -> Maybe ScalarExpr
> doCaseSimple a v whths els = do
> (whths',els') <- doCaseStuff a whths els
> return $ CaseSimple a v whths' els'
> doCaseStuff :: Annotation -> [([ScalarExpr],ScalarExpr)] -> Maybe ScalarExpr -> Maybe ([([ScalarExpr],ScalarExpr)],Maybe ScalarExpr)
> doCaseStuff a whths els = do
>
> expectedType <- atype a
>
> thenTypes <- mapM (atype . getAnnotation . snd) whths
>
> thenAndElseTypes <- case els of
> Nothing -> return thenTypes
> Just els' -> fmap (:thenTypes) $ atype $ getAnnotation els'
>
> when (all (==expectedType) thenAndElseTypes) Nothing
> return (map (fixWhTh expectedType) whths
> ,castElse expectedType)
> where
> castElse et = case els of
> Nothing -> Nothing
> Just els' | Just t' <- atype $ getAnnotation els
> , t' /= et
> -> Just (Cast ea els' $ typeName 4 et)
> | otherwise -> els
> fixWhTh :: Type -> ([ScalarExpr],ScalarExpr) -> ([ScalarExpr],ScalarExpr)
> fixWhTh et (whs,th) | Just t' <- atype $ getAnnotation th
> , t' /= et = (whs, Cast ea th $ typeName 5 et)
> | otherwise = (whs,th)
>
>
>
>
> canonicalizeTypeNames :: Data a => a -> a
> canonicalizeTypeNames = fixTypes . fixTypeNames
> where
> fixTypes =
> transformBi $ \x -> case x of
> ScalarType t -> ScalarType $ ct t
> x1 -> x1
> fixTypeNames =
> transformBi $ \x -> case x of
> SimpleTypeName a t -> SimpleTypeName a $ ct t
> PrecTypeName a t i -> PrecTypeName a (ct t) i
> Prec2TypeName a t i0 i1 -> Prec2TypeName a (ct t) i0 i1
> x1 -> x1
> ct = canonicalizeTypeName