aboutsummaryrefslogtreecommitdiff
path: root/src/Haddock/Utils/GHC.hs
blob: 3ac90d7797fdd0bd71f8c31343281eb93048695a (plain) (blame)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
--
-- Haddock - A Haskell Documentation Tool
--
-- (c) Simon Marlow 2003
--


module Haddock.Utils.GHC where


import Debug.Trace
import Data.Char

import GHC
import HsSyn
import SrcLoc
import HscTypes
import Outputable
import Packages
import UniqFM
import Name


-- names

nameOccString = occNameString . nameOccName 


nameSetMod n newMod = 
  mkExternalName (nameUnique n) newMod (nameOccName n) (nameSrcSpan n)


nameSetPkg pkgId n = 
  mkExternalName (nameUnique n) (mkModule pkgId (moduleName mod)) 
	               (nameOccName n) (nameSrcSpan n)
  where mod = nameModule n


-- modules


moduleString :: Module -> String
moduleString = moduleNameString . moduleName 


mkModuleNoPkg :: String -> Module
mkModuleNoPkg str = mkModule (stringToPackageId "") (mkModuleName str)


-- misc


-- there should be a better way to check this using the GHC API
isConSym n = head (nameOccString n) == ':'
isVarSym n = fstChar /= '_' && not (isConSym n) && (not . isLetter) fstChar
  where fstChar = head (nameOccString n)


getMainDeclBinder :: HsDecl name -> Maybe name
getMainDeclBinder (TyClD d) = Just (tcdName d)
getMainDeclBinder (ValD d)
   = case collectAcc d [] of
        []       -> Nothing 
        (name:_) -> Just (unLoc name)
getMainDeclBinder (SigD d) = sigNameNoLoc d
getMainDeclBinder (ForD (ForeignImport name _ _)) = Just (unLoc name)
getMainDeclBinder (ForD (ForeignExport name _ _)) = Nothing
getMainDeclBinder _ = Nothing


-- To keep if if minf_iface is re-introduced
--modInfoName = moduleName . mi_module . minf_iface
--modInfoMod  = mi_module . minf_iface 


trace_ppr x y = trace (showSDoc (ppr x)) y