module Language.Haskell.Refact.Utils.TypeSyn where
import qualified GHC as GHC
import qualified Name as GHC
import qualified Outputable as GHC
type HsExpP = GHC.HsExpr GHC.RdrName
type HsPatP = GHC.Pat GHC.RdrName
type HsDeclP = GHC.LHsDecl GHC.RdrName
type HsDeclsP = GHC.HsGroup GHC.Name
type InScopes = [GHC.Name]
type SimpPos = (Int,Int)
type PosToken = (GHC.Located GHC.Token, String)
type Export = GHC.LIE GHC.RdrName
type HsName = GHC.RdrName
newtype PName = PN HsName deriving (Eq)
instance Show GHC.NameSpace where
show ns
| ns == GHC.tcName = "TcClsName"
| ns == GHC.dataName = "DataName"
| ns == GHC.varName = "VarName"
| ns == GHC.tvName = "TvName"
| otherwise = "UnknownNamespace"
instance GHC.Outputable GHC.NameSpace where
ppr x = GHC.text $ show x
type HsModuleP = GHC.Located (GHC.HsModule GHC.RdrName)
ghead :: String -> [a] -> a
ghead info [] = error $ "ghead "++info++" []"
ghead _info (h:_) = h
glast :: String -> [a] -> a
glast info [] = error $ "glast " ++ info ++ " []"
glast _info h = last h
gtail :: String -> [a] -> [a]
gtail info [] = error $ "gtail " ++ info ++ " []"
gtail _info h = tail h
gfromJust :: [Char] -> Maybe a -> a
gfromJust _info (Just h) = h
gfromJust info Nothing = error $ "gfromJust " ++ info ++ " Nothing"