{-# LANGUAGE CPP #-}
module GHC.SourceGen.Type.Internal where
import HsTypes
import SrcLoc (Located, unLoc)
import GHC.SourceGen.Syntax.Internal
import GHC.SourceGen.Name.Internal
mkQTyVars :: [OccNameStr] -> LHsQTyVars'
mkQTyVars vars = withPlaceHolder
$ noExt (withPlaceHolder HsQTvs)
$ map (builtLoc . noExt UserTyVar . typeRdrName . UnqualStr)
vars
sigType :: HsType' -> LHsSigType'
sigType = implicitBndrs . builtLoc
implicitBndrs :: t -> HsImplicitBndrs' t
implicitBndrs = withPlaceHolder . noExt (withPlaceHolder HsTypes.HsIB)
parenthesizeTypeForApp, parenthesizeTypeForOp, parenthesizeTypeForFun
:: Located HsType' -> Located HsType'
parenthesizeTypeForApp t
| needsParenForApp (unLoc t) = parTy t
| otherwise = t
parenthesizeTypeForOp t
| needsParenForOp (unLoc t) = parTy t
| otherwise = t
parenthesizeTypeForFun t
| needsParenForFun (unLoc t) = parTy t
| otherwise = t
needsParenForFun, needsParenForOp, needsParenForApp
:: HsType' -> Bool
needsParenForFun t = case t of
HsForAllTy{} -> True
HsQualTy{} -> True
HsFunTy{} -> True
_ -> False
needsParenForOp t = case t of
HsOpTy{} -> True
_ -> needsParenForFun t
needsParenForApp t = case t of
HsAppTy {} -> True
_ -> needsParenForOp t
parTy :: Located HsType' -> Located HsType'
parTy = builtLoc . noExt HsParTy
sigWcType :: HsType' -> LHsSigWcType'
sigWcType = noExt (withPlaceHolder HsTypes.HsWC) . sigType
wcType :: HsType' -> LHsWcType'
wcType = noExt (withPlaceHolder HsTypes.HsWC) . builtLoc