aboutsummaryrefslogtreecommitdiff
path: root/src/HaskellCodeExplorer/GhcUtils.hs
blob: 89cd4bc71fed12eb42f29a2b998f97496c0a3c85 (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
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
186
187
188
189
190
191
192
193
194
195
196
197
198
199
200
201
202
203
204
205
206
207
208
209
210
211
212
213
214
215
216
217
218
219
220
221
222
223
224
225
226
227
228
229
230
231
232
233
234
235
236
237
238
239
240
241
242
243
244
245
246
247
248
249
250
251
252
253
254
255
256
257
258
259
260
261
262
263
264
265
266
267
268
269
270
271
272
273
274
275
276
277
278
279
280
281
282
283
284
285
286
287
288
289
290
291
292
293
294
295
296
297
298
299
300
301
302
303
304
305
306
307
308
309
310
311
312
313
314
315
316
317
318
319
320
321
322
323
324
325
326
327
328
329
330
331
332
333
334
335
336
337
338
339
340
341
342
343
344
345
346
347
348
349
350
351
352
353
354
355
356
357
358
359
360
361
362
363
364
365
366
367
368
369
370
371
372
373
374
375
376
377
378
379
380
381
382
383
384
385
386
387
388
389
390
391
392
393
394
395
396
397
398
399
400
401
402
403
404
405
406
407
408
409
410
411
412
413
414
415
416
417
418
419
420
421
422
423
424
425
426
427
428
429
430
431
432
433
434
435
436
437
438
439
440
441
442
443
444
445
446
447
448
449
450
451
452
453
454
455
456
457
458
459
460
461
462
463
464
465
466
467
468
469
470
471
472
473
474
475
476
477
478
479
480
481
482
483
484
485
486
487
488
489
490
491
492
493
494
495
496
497
498
499
500
501
502
503
504
505
506
507
508
509
510
511
512
513
514
515
516
517
518
519
520
521
522
523
524
525
526
527
528
529
530
531
532
533
534
535
536
537
538
539
540
541
542
543
544
545
546
547
548
549
550
551
552
553
554
555
556
557
558
559
560
561
562
563
564
565
566
567
568
569
570
571
572
573
574
575
576
577
578
579
580
581
582
583
584
585
586
587
588
589
590
591
592
593
594
595
596
597
598
599
600
601
602
603
604
605
606
607
608
609
610
611
612
613
614
615
616
617
618
619
620
621
622
623
624
625
626
627
628
629
630
631
632
633
634
635
636
637
638
639
640
641
642
643
644
645
646
647
648
649
650
651
652
653
654
655
656
657
658
659
660
661
662
663
664
665
666
667
668
669
670
671
672
673
674
675
676
677
678
679
680
681
682
683
684
685
686
687
688
689
690
691
692
693
694
695
696
697
698
699
700
701
702
703
704
705
706
707
708
709
710
711
712
713
714
715
716
717
718
719
720
721
722
723
724
725
726
727
728
729
730
731
732
733
734
735
736
737
738
739
740
741
742
743
744
745
746
747
748
749
750
751
752
753
754
755
756
757
758
759
760
761
762
763
764
765
766
767
768
769
770
771
772
773
774
775
776
777
778
779
780
781
782
783
784
785
786
787
788
789
790
791
792
793
794
795
796
797
798
799
800
801
802
803
804
805
806
807
808
809
810
811
812
813
814
815
816
817
818
819
820
821
822
823
824
825
826
827
828
829
830
831
832
833
834
835
836
837
838
839
840
841
842
843
844
845
846
847
848
849
850
851
852
853
854
855
856
857
858
859
860
861
862
863
864
865
866
867
868
869
870
871
872
873
874
875
876
877
878
879
880
881
882
883
884
885
886
887
888
889
890
891
892
893
894
895
896
897
898
899
900
901
902
903
904
905
906
907
908
909
910
911
912
913
914
915
916
917
918
919
920
921
922
923
924
925
926
927
928
929
930
931
932
933
934
935
936
937
938
939
940
941
942
943
944
945
946
947
948
949
950
951
952
953
954
955
956
957
958
959
960
961
962
963
964
965
966
967
968
969
970
971
972
973
974
975
976
977
978
979
980
981
982
983
984
985
986
987
988
989
990
991
992
993
994
995
996
997
998
999
1000
1001
1002
1003
1004
1005
1006
1007
1008
1009
1010
1011
1012
1013
1014
1015
1016
1017
1018
1019
1020
1021
1022
1023
1024
1025
1026
1027
1028
1029
1030
1031
1032
1033
1034
1035
1036
1037
1038
1039
1040
1041
1042
1043
1044
1045
1046
1047
1048
1049
1050
1051
1052
1053
1054
1055
1056
1057
1058
1059
1060
1061
1062
1063
1064
1065
1066
1067
1068
1069
1070
1071
1072
1073
1074
1075
1076
1077
1078
1079
1080
1081
1082
1083
1084
1085
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE TypeApplications #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE TupleSections #-}
{-# LANGUAGE Rank2Types #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE DuplicateRecordFields #-}
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE RecordWildCards #-}

module HaskellCodeExplorer.GhcUtils
  ( -- * Pretty-printing
    toText
  , instanceToText
  , instanceDeclToText
  , nameToText
  , tyClDeclPrefix
  , demangleOccName
  , stringBufferToByteString
  , nameSort
  , occNameNameSpace
  , identifierKey
  , nameKey
  , mbIdDetails
    -- * Syntax manipulation
  , hsGroupVals
  , hsPatSynDetails
  , ieLocNames
  , ghcDL
    -- * Lookups
  , lookupIdInTypeEnv
  , lookupNameModuleAndPackage
    -- * Location info
  , isHsBoot
  , moduleLocationInfo
  , nameLocationInfo
  , occNameLocationInfo
  , nameDocumentation
  , srcSpanToLineAndColNumbers
    -- * Type-related functions
  , tyThingToId
  , tidyIdentifierType
  , patSynId
  , applyWrapper
  , wrapperTypes
  , tyVarsOfType
  , tyConsOfType
  , updateOccNames
  , mkType
    -- * Documentation processing
  , collectDocs
  , ungroup
  , mkDecls
  , getMainDeclBinder
  , classDeclDocs
  , sigNameNoLoc
  , clsInstDeclSrcSpan
  , hsDocsToDocH
  , subordinateNamesWithDocs
  ) where
import qualified Data.ByteString               as BS
import qualified Data.ByteString.Internal      as BSI
import           Data.Char                      ( isAlpha
                                                , isAlphaNum
                                                , isAscii
                                                , ord
                                                )
import           Data.Generics                  ( Data )
import           Data.Generics.SYB              ( everything
                                                , everywhere
                                                , mkQ
                                                , mkT
                                                )
import qualified Data.Generics.Uniplate.Data    ( )
import qualified Data.HashMap.Strict           as HM
import           Data.Hashable                  ( Hashable
                                                , hash
                                                )
import qualified Data.List                     as L
import           Data.Maybe                     ( fromMaybe
                                                , isJust
                                                , mapMaybe
                                                )
import qualified Data.Text                     as T
import           Documentation.Haddock.Parser   ( overIdentifier
                                                , parseParas
                                                )
import           Documentation.Haddock.Types    ( DocH(..)
                                                , Header(..)
                                                , Namespace
                                                , _doc
                                                )
import           GHC                            ( ClsInstDecl(..)
                                                , CollectFlag(..)
                                                , ConDecl(..)
                                                , ConDeclField(..)
                                                , DataFamInstDecl(..)
                                                , DynFlags
                                                , FamEqn(..)
                                                , FixitySig(..)
                                                , ForeignDecl(..)
                                                , GhcPass
                                                , HsConDetails(..)
                                                , HsDataDefn(..)
                                                , HsDecl(..)
                                                , HsDocString
                                                , HsGroup(..)
                                                , HsPatSynDetails
                                                , HsValBindsLR(..)
                                                , IE(..)
                                                , Id
                                                , InstDecl(..)
                                                , LHsBindLR
                                                , LHsDecl
                                                , LIEWrappedName
                                                , Located
                                                , NHsValBindsLR(..)
                                                , Name
                                                , NewOrData(..)
                                                , NoExtField(..)
                                                , RealSrcSpan(..)
                                                , Sig(..)
                                                , SrcSpan(..)
                                                , TyClDecl(..)
                                                , TyThing(..)
                                                , UnXRec
                                                , collectHsBindBinders
                                                , extFieldOcc
                                                , getConNames
                                                , getLocA
                                                , getRecConArgs_maybe
                                                , idType
                                                , ieLWrappedName
                                                , isDataFamilyDecl
                                                , isExternalName
                                                , isGoodSrcSpan
                                                , isLocalId
                                                , nameSrcSpan
                                                , rdrNameFieldOcc
                                                , reLocN
                                                , recordPatSynField
                                                , recordPatSynPatVar
                                                , sortLocatedA
                                                , srcSpanEndCol
                                                , srcSpanEndLine
                                                , srcSpanFile
                                                , srcSpanStartCol
                                                , srcSpanStartLine
                                                , tcdName
                                                , tfid_eqn
                                                , tyConKind
                                                , tyFamInstDeclName
                                                , unXRec
                                                , unpackHDS
                                                )
import           GHC.Core.ConLike               ( ConLike(..) )
import           GHC.Core.DataCon               ( dataConWorkId )
import           GHC.Data.Bag                   ( bagToList )
import           GHC.Data.FastString            ( mkFastString
                                                , unpackFS
                                                )
import           GHC.HsToCore.Docs              ( collectDocs
                                                , mkDecls
                                                , ungroup
                                                )

import           GHC.Builtin.Types              ( unitTy )
import           GHC.Core.InstEnv               ( ClsInst(..) )
import           GHC.Core.PatSyn                ( PatSyn
                                                , patSynMatcher
                                                , patSynSig
                                                )
import           GHC.Core.TyCo.Ppr              ( pprSigmaType )
import           GHC.Core.TyCo.Rep              ( Type(..)
                                                , mkVisFunTyMany
                                                , mkVisFunTys
                                                , mkVisFunTysMany
                                                , scaledThing
                                                )
import           GHC.Core.TyCon                 ( tyConName )
import           GHC.Core.Type                  ( coreView
                                                , expandTypeSynonyms
                                                , mkForAllTy
                                                , mkTyCoInvForAllTys
                                                , piResultTy
                                                , splitFunTy_maybe
                                                , tidyOpenType
                                                )
import           GHC.CoreToIface
import           GHC.Data.Pair                  ( pSnd )
import           GHC.Data.StringBuffer          ( StringBuffer(..)
                                                , stringToStringBuffer
                                                )
import           GHC.Driver.Config              ( initParserOpts )
import           GHC.Driver.Ppr                 ( showPpr
                                                , showSDoc
                                                )
import           GHC.Hs.Extension               ( GhcRn )
import           GHC.Iface.Type
import           GHC.Parser                     ( parseIdentifier )
import           GHC.Parser.Lexer               ( ParseResult(POk)
                                                , initParserState
                                                , unP
                                                )
import           GHC.Rename.Env                 ( dataTcOccs )
import           GHC.Tc.Types.Evidence          ( HsWrapper(..)
                                                , tcCoercionKind
                                                )
import           GHC.Tc.Utils.TcType            ( evVarPred )
import           GHC.Types.Id.Info              ( IdDetails(..) )
import           GHC.Types.Name                 ( isDataConNameSpace
                                                , isDerivedOccName
                                                , isInternalName
                                                , isSystemName
                                                , isTvNameSpace
                                                , isTyConName
                                                , isValNameSpace
                                                , isWiredInName
                                                , mkInternalName
                                                , mkOccName
                                                , nameModule_maybe
                                                , nameOccName
                                                , nameUnique
                                                , occNameFS
                                                , occNameSpace
                                                , occNameString
                                                , wiredInNameTyThing_maybe
                                                )
import           GHC.Types.Name.Occurrence      ( OccName )
import           GHC.Types.Name.Reader          ( GlobalRdrEnv
                                                , RdrName(..)
                                                , grePrintableName
                                                , lookupGRE_RdrName
                                                )
import           GHC.Types.SrcLoc               ( GenLocated(..)
                                                , mkRealSrcLoc
                                                , unLoc
                                                )
import           GHC.Types.TypeEnv              ( TypeEnv
                                                , lookupTypeEnv
                                                )
import           GHC.Types.Unique               ( getKey )
import           GHC.Types.Unique.Set           ( emptyUniqSet
                                                , nonDetEltsUniqSet
                                                , unionUniqSets
                                                )
import           GHC.Types.Var                  ( idDetails
                                                , isId
                                                , mkCoVar
                                                , mkTyVar
                                                , setVarType
                                                , varName
                                                , varType
                                                , varUnique
                                                )
import           GHC.Types.Var.Env              ( TidyEnv )
import           GHC.Types.Var.Set              ( VarSet
                                                , emptyVarSet
                                                , unionVarSet
                                                , unitVarSet
                                                )
import           GHC.Unit
import           GHC.Unit.State                 ( LookupResult(..)
                                                , lookupModuleWithSuggestions
                                                , lookupUnit
                                                )
import           GHC.Utils.Outputable           ( Outputable
                                                , ppr
                                                )
import qualified HaskellCodeExplorer.Types     as HCE
import           Language.Haskell.Syntax.Extension
                                                ( IdP )
import           Prelude                 hiding ( id
                                                , span
                                                )
import           System.FilePath                ( normalise )

--------------------------------------------------------------------------------
-- Pretty-printing
--------------------------------------------------------------------------------

toText :: (Outputable a) => DynFlags -> a -> T.Text
toText flags = T.pack . showSDoc flags . ppr

instanceToText :: DynFlags -> ClsInst -> T.Text
instanceToText flags ClsInst {..} =
  T.append "instance " $ T.pack . showSDoc flags $ pprSigmaType (idType is_dfun)

instanceDeclToText :: DynFlags -> InstDecl GhcRn -> T.Text
instanceDeclToText flags decl = case decl of
-- Pattern match has inaccessible right hand side
    -- XInstDecl _ -> ""
    -- ClsInstD _ (XClsInstDecl _) -> ""
  ClsInstD _ ClsInstDecl {..} ->
    T.append "instance " (toText flags cid_poly_ty)
  DataFamInstD _ di ->
    let args =
          T.intercalate " " . map (toText flags) . feqn_pats . dfid_eqn $ di
    in  T.concat
          [ "data instance "
          , toText flags (unLoc $ feqn_tycon . dfid_eqn $ di)
          , " "
          , args
          ]
  TyFamInstD _ ti ->
    let args =
          T.intercalate " " . map (toText flags) . feqn_pats . tfid_eqn $ ti
    in  T.concat
          ["type instance ", toText flags $ tyFamInstDeclName ti, " ", args]

nameToText :: Name -> T.Text
nameToText = T.pack . unpackFS . occNameFS . nameOccName

tyClDeclPrefix :: TyClDecl a -> T.Text
tyClDeclPrefix tyClDecl =
  let isNewTy :: TyClDecl a -> Bool
      isNewTy DataDecl { tcdDataDefn = HsDataDefn { dd_ND = NewType } } = True
      isNewTy _ = False
  in  case tyClDecl of
        FamDecl{} | isDataFamilyDecl tyClDecl -> "data family "
                  | otherwise                 -> "type family "
        SynDecl{} -> "type "
        DataDecl{} | isNewTy tyClDecl -> "newtype "
                   | otherwise        -> "data "
        ClassDecl{} -> "class "
        XTyClDecl _ -> ""

demangleOccName :: Name -> T.Text
demangleOccName name
  | isDerivedOccName (nameOccName name)
  = let removePrefix :: T.Text -> T.Text
        removePrefix occName
          | T.isPrefixOf "$sel:" occName = fst
          $ T.breakOn ":" (T.drop 5 occName)
          | T.isPrefixOf "$W" occName = T.drop 2 occName
          | T.isPrefixOf "$w" occName = T.drop 2 occName
          | T.isPrefixOf "$m" occName = T.drop 2 occName
          | T.isPrefixOf "$b" occName = T.drop 2 occName
          | T.isPrefixOf "$dm" occName = T.drop 3 occName
          | T.isPrefixOf "$c" occName = T.drop 2 occName
          | T.isPrefixOf "$d" occName = T.drop 2 occName
          | T.isPrefixOf "$i" occName = T.drop 2 occName
          | T.isPrefixOf "$s" occName = T.drop 2 occName
          | T.isPrefixOf "$f" occName = T.drop 2 occName
          | T.isPrefixOf "$r" occName = T.drop 2 occName
          | T.isPrefixOf "C:" occName = T.drop 2 occName
          | T.isPrefixOf "N:" occName = T.drop 2 occName
          | T.isPrefixOf "D:" occName = T.drop 2 occName
          | T.isPrefixOf "$co" occName = T.drop 3 occName
          | otherwise = occName
    in  removePrefix $ nameToText name
  | otherwise
  = nameToText name

stringBufferToByteString :: StringBuffer -> BS.ByteString
stringBufferToByteString (StringBuffer buf len cur) =
  BSI.fromForeignPtr buf cur len

nameSort :: Name -> HCE.NameSort
nameSort n = if isExternalName n then HCE.External else HCE.Internal

occNameNameSpace :: OccName -> HCE.NameSpace
occNameNameSpace n | isDataConNameSpace (occNameSpace n) = HCE.DataName
                   | isTvNameSpace (occNameSpace n)      = HCE.TvName
                   | isValNameSpace (occNameSpace n)     = HCE.VarName
                   | otherwise                           = HCE.TcClsName

-- Two 'Id''s may have different types even though they have the same 'Unique'.
identifierKey :: DynFlags -> Id -> T.Text
identifierKey flags id | isLocalId id = T.concat
  [ T.pack . show . getKey . varUnique $ id
  , "_"
  , T.pack . show . hash . showSDoc flags . ppr . varType $ id
  ]
identifierKey _ id = T.pack . show . getKey . varUnique $ id

nameKey :: Name -> T.Text
nameKey = T.pack . show . getKey . nameUnique

mbIdDetails :: Id -> Maybe HCE.IdDetails
mbIdDetails v | isId v = case idDetails v of
  VanillaId                        -> Just HCE.VanillaId
  RecSelId { sel_naughty = False } -> Just HCE.RecSelId
  RecSelId { sel_naughty = True }  -> Just HCE.RecSelIdNaughty
  DataConWorkId _                  -> Just HCE.DataConWorkId
  DataConWrapId _                  -> Just HCE.DataConWrapId
  ClassOpId     _                  -> Just HCE.ClassOpId
  PrimOpId      _                  -> Just HCE.PrimOpId
  FCallId       _                  -> Just HCE.FCallId
  TickBoxOpId   _                  -> Just HCE.TickBoxOpId
  DFunId        _                  -> Just HCE.DFunId
  CoVarId                          -> Just HCE.CoVarId
  JoinId _                         -> Just HCE.JoinId
mbIdDetails _ = Nothing

--------------------------------------------------------------------------------
--  Syntax transformation
--------------------------------------------------------------------------------

hsGroupVals :: HsGroup GhcRn -> [LHsBindLR GhcRn GhcRn]
hsGroupVals hsGroup =
  filter (isGoodSrcSpan . getLocA) $ case hs_valds hsGroup of
    XValBindsLR (NValBinds binds _) -> concatMap (bagToList . snd) binds
    _                               -> []

hsPatSynDetails :: HsPatSynDetails GhcRn -> [Located Name]
hsPatSynDetails patDetails = case patDetails of
  InfixCon  name1 name2  -> [reLocN name1, reLocN name2]
  PrefixCon _     fields -> reLocN <$> fields
  RecCon fields          -> concatMap
    (\field ->
      [ L ((getLocA . rdrNameFieldOcc . recordPatSynField) field)
          (extFieldOcc $ recordPatSynField field)
      , reLocN $ recordPatSynPatVar field
      ]
    )
    fields

unwrapName :: LIEWrappedName a -> Located a
unwrapName = reLocN . ieLWrappedName

ieLocNames :: IE pass -> [Located (IdP pass)]

ieLocNames (XIE _               ) = []
ieLocNames (IEVar      _ n      ) = [unwrapName n]
ieLocNames (IEThingAbs _ n      ) = [unwrapName n]
ieLocNames (IEThingAll _ n      ) = [unwrapName n]
ieLocNames (IEThingWith _ n _ ns) = unwrapName n : (map unwrapName ns)
ieLocNames IEModuleContents{}     = []
ieLocNames IEGroup{}              = []
ieLocNames IEDoc{}                = []
ieLocNames IEDocNamed{}           = []

--------------------------------------------------------------------------------
-- Lookups
--------------------------------------------------------------------------------

lookupIdInTypeEnv :: TypeEnv -> Name -> Maybe Id
lookupIdInTypeEnv typeEnv name = do
  let mbTyThing | isInternalName name = Nothing
                | isSystemName name   = Nothing
                | isWiredInName name  = wiredInNameTyThing_maybe name
                | isExternalName name = lookupTypeEnv typeEnv name
                | otherwise           = Nothing
  case mbTyThing of
    Just tyThing -> tyThingToId tyThing
    _            -> Nothing

lookupNameModuleAndPackage
  :: UnitState
  -> HCE.PackageId
  -> Name
  -> Either T.Text (HCE.HaskellModuleName, HCE.PackageId)
lookupNameModuleAndPackage state currentPackageId name =
  case nameModule_maybe name of
    Just Module {..} -> case lookupUnit state moduleUnit of
      Just unitInfo ->
        let packageId =
              if (T.pack . unitPackageNameString $ unitInfo)
                   == HCE.name (currentPackageId :: HCE.PackageId)
                then currentPackageId
                else HCE.PackageId (T.pack $ unitPackageNameString unitInfo)
                                   (unitPackageVersion unitInfo)
        in  Right
              ( HCE.HaskellModuleName . T.pack . moduleNameString $ moduleName
              , packageId
              )
      Nothing -> Right
        ( HCE.HaskellModuleName . T.pack . moduleNameString $ moduleName
        , currentPackageId
        )
    Nothing ->
      Left $ T.concat ["nameModule_maybe ", nameToText name, " is Nothing"]

--------------------------------------------------------------------------------
-- Location info
--------------------------------------------------------------------------------

isHsBoot :: HCE.HaskellModulePath -> Bool
isHsBoot = T.isSuffixOf "-boot" . HCE.getHaskellModulePath

moduleLocationInfo
  :: UnitState
  -> HM.HashMap
       HCE.HaskellModuleName
       (HM.HashMap HCE.ComponentId HCE.HaskellModulePath)
  -> HCE.PackageId
  -> HCE.ComponentId
  -> ModuleName
  -> HCE.LocationInfo
moduleLocationInfo unitState moduleNameMap currentPackageId compId moduleName =
  let moduleNameText         = T.pack . moduleNameString $ moduleName
      currentPackageLocation = HCE.ApproximateLocation
        currentPackageId
        (HCE.HaskellModuleName . T.pack . moduleNameString $ moduleName)
        HCE.Mod
        moduleNameText
        Nothing
        compId
  in  case HM.lookup (HCE.HaskellModuleName moduleNameText) moduleNameMap of
        Just modulePathMap
          | Just modulePath <- HM.lookup compId modulePathMap -> HCE.ExactLocation
            currentPackageId
            modulePath
            (HCE.HaskellModuleName moduleNameText)
            1
            1
            1
            1
        _ -> case lookupModuleWithSuggestions unitState moduleName Nothing of
          LookupFound Module { moduleUnit = unitId } _ ->
            case lookupUnit unitState unitId of
              Just unitInfo ->
                let packageId = HCE.PackageId
                      (T.pack $ unitPackageNameString unitInfo)
                      (unitPackageVersion unitInfo)
                in  HCE.ApproximateLocation
                      packageId
                      ( HCE.HaskellModuleName
                      . T.pack
                      . moduleNameString
                      $ moduleName
                      )
                      HCE.Mod
                      moduleNameText
                      Nothing
                      (if packageId == currentPackageId
                        then compId
                        else HCE.ComponentId "lib"
                      )
              Nothing -> currentPackageLocation
          _ -> currentPackageLocation

isDefinedInCurrentModule
  :: HCE.SourceCodeTransformation -> HCE.HaskellFilePath -> Bool
isDefinedInCurrentModule transformation file =
  let includedFiles = HM.keys $ HCE.fileIndex transformation
      modPath       = HCE.getHaskellModulePath
        $ HCE.filePath (transformation :: HCE.SourceCodeTransformation)
  in  HCE.getHaskellFilePath file == modPath || (file `elem` includedFiles)

nameLocationInfo
  :: UnitState
  -> HCE.PackageId
  -> HCE.ComponentId
  -> HCE.SourceCodeTransformation
  -> HM.HashMap HCE.HaskellFilePath HCE.HaskellModulePath
  -> HM.HashMap HCE.HaskellModulePath HCE.DefinitionSiteMap
  -> Maybe T.Text -- ^ Instance head (when name is a dictionary function)
  -> Maybe SrcSpan -- ^ Only for wired-in names
  -> Name
  -> HCE.LocationInfo
nameLocationInfo unitState currentPackageId compId transformation fileMap defSiteMap mbInstanceHead mbSrcSpan name
  | Just srcSpan <- realSrcSpan name mbSrcSpan
  = let
      filePath =
        HCE.HaskellFilePath
          . T.pack
          . normalise
          . unpackFS
          . srcSpanFile
          $ srcSpan
      approximateLocation = mkApproximateLocation unitState
                                                  currentPackageId
                                                  compId
                                                  mbInstanceHead
                                                  name
    in
      if isDefinedInCurrentModule transformation filePath
        then
          let
            eitherStart = HCE.fromOriginalLineNumber
              transformation
              (filePath, srcSpanStartLine srcSpan)
            eitherEnd = HCE.fromOriginalLineNumber
              transformation
              (filePath, srcSpanEndLine srcSpan)
          in
            case (,) eitherStart eitherEnd of
              (Right startLine, Right endLine) ->
                let
                  modulePath = HCE.filePath
                    (transformation :: HCE.SourceCodeTransformation)
                  moduleName = either
                    (const $ HCE.HaskellModuleName "")
                    fst
                    (lookupNameModuleAndPackage unitState currentPackageId name)
                in
                  HCE.ExactLocation { packageId   = currentPackageId
                                    , modulePath  = modulePath
                                    , moduleName  = moduleName
                                    , startLine   = startLine
                                    , endLine     = endLine
                                    , startColumn = srcSpanStartCol srcSpan
                                    , endColumn   = srcSpanEndCol srcSpan
                                    }
              _ -> approximateLocation
        else case HM.lookup filePath fileMap of
          Just haskellModulePath ->
            case HM.lookup haskellModulePath defSiteMap of
              Just defSites ->
                let key = fromMaybe (nameToText name) mbInstanceHead
                in  lookupEntityLocation
                      defSites
                      (mkLocatableEntity name mbInstanceHead)
                      key
              Nothing -> approximateLocation
          Nothing -> approximateLocation
 where
  realSrcSpan :: Name -> Maybe SrcSpan -> Maybe RealSrcSpan
  realSrcSpan n mbSpan = case nameSrcSpan n of
    RealSrcSpan span _  -> Just span
    _ | isWiredInName n -> case mbSpan of
      Just span -> case span of
        RealSrcSpan s _ -> Just s
        _               -> Nothing
      _ -> Nothing
    _ -> Nothing
nameLocationInfo unitState currentPackageId compId _transformation _fileMap _defSiteMap mbInstanceHead _mbSrcSpan name
  = mkApproximateLocation unitState currentPackageId compId mbInstanceHead name

mkApproximateLocation
  :: UnitState
  -> HCE.PackageId
  -> HCE.ComponentId
  -> Maybe T.Text
  -> Name
  -> HCE.LocationInfo
mkApproximateLocation unitState currentPackageId compId mbInstanceHead name =
  let haddockAnchor =
        Just . T.pack . makeAnchorId . T.unpack . nameToText $ name
  in  case lookupNameModuleAndPackage unitState currentPackageId name of
        Right (moduleName, packageId) -> HCE.ApproximateLocation
          { moduleName      = moduleName
          , packageId       = packageId
          , componentId     = if packageId == currentPackageId
                                then compId
                                else HCE.ComponentId "lib"
          , entity          = mkLocatableEntity name mbInstanceHead
          , haddockAnchorId = haddockAnchor
          , name            = fromMaybe (nameToText name) mbInstanceHead
          }
        Left errorMessage -> HCE.UnknownLocation errorMessage

mkLocatableEntity :: Name -> Maybe a -> HCE.LocatableEntity
mkLocatableEntity name mbInstanceHead
  | isJust mbInstanceHead = HCE.Inst
  | otherwise = case occNameNameSpace . nameOccName $ name of
    HCE.VarName  -> HCE.Val
    HCE.DataName -> HCE.Val
    _            -> HCE.Typ

occNameLocationInfo
  :: DynFlags
  -> HCE.PackageId
  -> HCE.ComponentId
  -> (ModuleName, OccName)
  -> HCE.LocationInfo
occNameLocationInfo flags packageId componentId (modName, occName) =
  HCE.ApproximateLocation
    { packageId       = packageId
    , moduleName      = HCE.HaskellModuleName $ toText flags modName
    , entity          = case occNameNameSpace occName of
                          HCE.VarName  -> HCE.Val
                          HCE.DataName -> HCE.Val
                          _            -> HCE.Typ
    , name            = toText flags occName
    , haddockAnchorId = Just . T.pack . makeAnchorId . T.unpack $ toText
                          flags
                          occName
    , componentId     = componentId
    }

lookupEntityLocation
  :: HCE.DefinitionSiteMap -> HCE.LocatableEntity -> T.Text -> HCE.LocationInfo
lookupEntityLocation defSiteMap locatableEntity text =
  let errorMessage = T.concat
        ["Cannot find location of ", T.pack . show $ locatableEntity, " ", text]
      defSiteLocation = HCE.location :: HCE.DefinitionSite -> HCE.LocationInfo
      lookupLocation
        :: (Eq a, Hashable a)
        => (HCE.DefinitionSiteMap -> HM.HashMap a HCE.DefinitionSite)
        -> (T.Text -> a)
        -> HCE.LocationInfo
      lookupLocation selector toKey =
        maybe (HCE.UnknownLocation errorMessage) defSiteLocation
          $ HM.lookup (toKey text) (selector defSiteMap)
  in  case locatableEntity of
        HCE.Val  -> lookupLocation HCE.values HCE.OccName
        HCE.Typ  -> lookupLocation HCE.types HCE.OccName
        HCE.Inst -> lookupLocation HCE.instances (\t -> t)
        HCE.Mod  -> HCE.UnknownLocation errorMessage

nameDocumentation
  :: HCE.SourceCodeTransformation
  -> HM.HashMap HCE.HaskellFilePath HCE.HaskellModulePath
  -> HM.HashMap HCE.HaskellModulePath HCE.DefinitionSiteMap
  -> HCE.DefinitionSiteMap
  -> Name
  -> Maybe T.Text
nameDocumentation transformation fileMap defSiteMap currentModuleDefSiteMap name
  | isExternalName name || isWiredInName name
  , Just file <- srcSpanToFilePath . nameSrcSpan $ name
  = if isDefinedInCurrentModule transformation file
    then lookupNameDocumentation name currentModuleDefSiteMap
    else case HM.lookup file fileMap of
      Just haskellModulePath -> case HM.lookup haskellModulePath defSiteMap of
        Just defSites -> lookupNameDocumentation name defSites
        Nothing       -> Nothing
      Nothing -> Nothing
nameDocumentation _ _ _ _ _ = Nothing

lookupNameDocumentation :: Name -> HCE.DefinitionSiteMap -> Maybe T.Text
lookupNameDocumentation name defSiteMap =
  let key = HCE.OccName $ nameToText name
      lookupDoc
        :: (HCE.DefinitionSiteMap -> HM.HashMap HCE.OccName HCE.DefinitionSite)
        -> Maybe T.Text
      lookupDoc selector = maybe Nothing HCE.documentation
        $ HM.lookup key (selector (defSiteMap :: HCE.DefinitionSiteMap))
  in  case occNameNameSpace . nameOccName $ name of
        HCE.VarName  -> lookupDoc HCE.values
        HCE.DataName -> lookupDoc HCE.values
        _            -> lookupDoc HCE.types

srcSpanToFilePath :: SrcSpan -> Maybe HCE.HaskellFilePath
srcSpanToFilePath (RealSrcSpan s _) =
  Just . HCE.HaskellFilePath . T.pack . normalise . unpackFS . srcSpanFile $ s
srcSpanToFilePath (UnhelpfulSpan _) = Nothing

srcSpanToLineAndColNumbers
  :: HCE.SourceCodeTransformation
  -> SrcSpan
  -> Maybe (HCE.HaskellFilePath, (Int, Int), (Int, Int))
-- do we need to do anything with the BufSpan?
srcSpanToLineAndColNumbers transformation (RealSrcSpan s _) =
  let filePath =
        HCE.HaskellFilePath . T.pack . normalise . unpackFS . srcSpanFile $ s
      eitherStart =
        HCE.fromOriginalLineNumber transformation (filePath, srcSpanStartLine s)
      eitherEnd =
        HCE.fromOriginalLineNumber transformation (filePath, srcSpanEndLine s)
  in  case (,) eitherStart eitherEnd of
        (Right startLine, Right endLine) ->
          Just
            ( filePath
            , (startLine, srcSpanStartCol s)
            , (endLine  , srcSpanEndCol s)
            )
        _ -> Nothing
srcSpanToLineAndColNumbers _ _ = Nothing

--------------------------------------------------------------------------------
-- Type-related functions
--------------------------------------------------------------------------------

tyThingToId :: TyThing -> Maybe Id
tyThingToId tyThing = case tyThing of
  AnId     id  -> Just id
  ATyCon   tc  -> Just $ mkTyVar (tyConName tc) (tyConKind tc)
  AConLike con -> case con of
    RealDataCon dataCon -> Just $ dataConWorkId dataCon
    PatSynCon   ps      -> Just $ patSynId ps
  ACoAxiom _ -> Nothing

tidyIdentifierType :: TidyEnv -> Id -> (TidyEnv, Id)
tidyIdentifierType tidyEnv identifier =
  let (tidyEnv', typ') = tidyOpenType tidyEnv (varType identifier)
  in  (tidyEnv', setVarType identifier typ')

patSynId :: PatSyn -> Id
patSynId patSyn =
  let (univTvs, reqTheta, exTvs, provTheta, argTys, resTy) = patSynSig patSyn
      reqTheta'
        | null reqTheta && not (null provTheta && null exTvs) = [unitTy]
        | otherwise = reqTheta
      --  required => provided => arg_1 -> ... -> arg_n -> res
      patSynTy =
        mkTyCoInvForAllTys univTvs
          $ mkVisFunTysMany reqTheta'
          $ mkTyCoInvForAllTys exTvs
          $ mkVisFunTysMany provTheta
          $ mkVisFunTys argTys resTy
      (name, _, _) = patSynMatcher patSyn
  in  mkCoVar name patSynTy

applyWrapper :: HsWrapper -> Type -> Type
applyWrapper wp ty | Just ty' <- coreView ty = applyWrapper wp ty'
applyWrapper WpHole                t         = t
applyWrapper (WpCompose w1 w2) t = applyWrapper w1 . applyWrapper w2 $ t
applyWrapper (WpFun w1 w2 t1 _doc) t         = mkVisFunTys
  [t1]
  (applyWrapper w2 $ piResultTy t (applyWrapper w1 $ scaledThing t1))
applyWrapper (WpCast  coercion) _t = pSnd $ tcCoercionKind coercion
applyWrapper (WpEvLam v       ) t  = mkVisFunTyMany (evVarPred v) t
applyWrapper (WpEvApp _ev     ) t  = case splitFunTy_maybe t of
  Just (_, _arg, res) -> res
  Nothing             -> t
applyWrapper (WpTyLam        v       ) t = mkForAllTy v Required t
applyWrapper (WpTyApp        t'      ) t = piResultTy t t'
applyWrapper (WpLet          _       ) t = t
applyWrapper (WpMultCoercion coercion) _ = pSnd $ tcCoercionKind coercion

wrapperTypes :: HsWrapper -> [Type]
wrapperTypes WpHole             = []
wrapperTypes (WpCompose w1 w2 ) = wrapperTypes w2 ++ wrapperTypes w1
wrapperTypes (WpFun w1 w2 _ _ ) = wrapperTypes w2 ++ wrapperTypes w1
wrapperTypes (WpCast         _) = []
wrapperTypes (WpEvLam        _) = []
wrapperTypes (WpEvApp        _) = []
wrapperTypes (WpTyLam        _) = []
wrapperTypes (WpTyApp        t) = [t]
wrapperTypes (WpLet          _) = []
wrapperTypes (WpMultCoercion _) = []

mkType :: DynFlags -> Type -> HCE.Type
mkType flags typ =
  let typeExpanded           = expandTypeSynonyms typ
      typeComponents         = toTypeComponents flags typ
      typeComponentsExpanded = toTypeComponents flags typeExpanded
  in  HCE.Type
        typeComponents
        (if typeComponents /= typeComponentsExpanded
          then Just typeComponentsExpanded
          else Nothing
        )

typeToText :: DynFlags -> Type -> T.Text
typeToText flags = T.pack . showSDoc flags . pprIfaceType . toIfaceType

toTypeComponents :: DynFlags -> Type -> [HCE.TypeComponent]
toTypeComponents flags typ =
  let signature = typeToText flags $ updateOccNames
        (\_unique occName -> ";" ++ drop 2 occName ++ ";")
        typ
      -- Signature with OccNames and uniques
      signatureWithUniques = typeToText flags $ updateOccNames
        (\unique occName -> ";," ++ occName ++ "," ++ unique ++ ";")
        typ
      -- Dirty but simple way to extract a list of TypeComponent from a type signature.
      -- Assumptions :
      -- 1. Character ';' cannot appear anywhere in a type signature
      -- 2. Character ',' cannot appear in an 'OccName'
      -- 3. length (T.splitOn ";" signature) == length (T.splitOn ";" signatureWithUniques)
      components =
        L.zip (T.splitOn ";" signature) (T.splitOn ";" signatureWithUniques)
  in  mapMaybe
        (\(text1, text2) -> if T.isPrefixOf "," text2
          then case T.splitOn "," text2 of
            ["", name, id] ->
              Just HCE.TyCon { name = name, internalId = HCE.InternalId id }
            _ -> Just $ HCE.Text text1
          else if T.null text1 then Nothing else Just $ HCE.Text text1
        )
        components

-- | Replaces 'OccName' of each type variable and type constructor in a type.
updateOccNames :: (String -> String -> String) -> Type -> Type
updateOccNames update = everywhere (mkT updateType)
 where
  updateType :: Type -> Type
  updateType (TyVarTy var) = TyVarTy var { varName = updateName (varName var) }
  updateType (TyConApp con args) =
    TyConApp (con { tyConName = updateName (tyConName con) }) args
  updateType other = other
  updateName :: Name -> Name
  updateName oldName =
    let
      oldOccName = nameOccName oldName
      unique     = T.unpack $ nameKey oldName
      newOccName = mkOccName (occNameSpace oldOccName)
                             (update unique (occNameString oldOccName))
    in
      mkInternalName (nameUnique oldName) newOccName (nameSrcSpan oldName)

-- | This function doesn't look through type synonyms
tyConsOfType :: Type -> [Id]
tyConsOfType = nonDetEltsUniqSet
  . everything unionUniqSets (emptyVarSet `mkQ` tyCon)
 where
  tyCon :: Type -> VarSet
  tyCon (TyConApp tc _) = unitVarSet $ mkTyVar (tyConName tc) (tyConKind tc)
  tyCon _               = emptyUniqSet

tyVarsOfType :: (Data a) => a -> [Id]
tyVarsOfType = nonDetEltsUniqSet
  . everything unionVarSet (emptyVarSet `mkQ` tyVar)
 where
  tyVar :: Type -> VarSet
  tyVar (TyVarTy ty) = unitVarSet ty
  tyVar _            = emptyVarSet

--------------------------------------------------------------------------------
-- Documentation processing
-- Some functions are copied from haddock-api package
--------------------------------------------------------------------------------

-- available in GHC.HsToCore.Docs
-- collectDocs :: [LHsDecl p] -> [(LHsDecl p, [HsDocString])]
-- ungroup :: HsGroup GhcRn -> [LHsDecl GhcRn]
-- Take a field of declarations from a data structure and create HsDecls using the given constructor
-- mkDecls :: (struct -> [GenLocated l decl]) -> (decl -> hsDecl) -> struct -> [GenLocated l hsDecl]

classDeclDocs :: TyClDecl GhcRn -> [(LHsDecl GhcRn, [HsDocString])]
classDeclDocs class_ = collectDocs . sortLocatedA $ decls
 where
  decls = docs ++ defs ++ sigs ++ ats
  docs  = mkDecls tcdDocs (DocD NoExtField) class_
  defs  = mkDecls (bagToList . tcdMeths) (ValD NoExtField) class_
  sigs  = mkDecls tcdSigs (SigD NoExtField) class_
  ats   = mkDecls tcdATs ((TyClD NoExtField) . (FamDecl NoExtField)) class_


conDeclDocs :: ConDecl GhcRn -> [(Name, [HsDocString], SrcSpan)]
conDeclDocs conDecl =
  map
      (\con ->
        (unLoc con, maybe [] ((: []) . unLoc) $ con_doc conDecl, getLocA con)
      )
    . getConNames
    $ conDecl

selectorDocs :: ConDecl GhcRn -> [(Name, [HsDocString], SrcSpan)]
selectorDocs con = case getRecConArgs_maybe con of
  Just (L _ flds) -> concatMap
    (\(L _ (ConDeclField _ fieldOccs _ mbDoc)) -> map
      (\(L span f) -> (extFieldOcc f, maybe [] ((: []) . unLoc) mbDoc, span))
      fieldOccs
    )
    flds
  _ -> []

subordinateNamesWithDocs :: [LHsDecl GhcRn] -> [(Name, [HsDocString], SrcSpan)]
subordinateNamesWithDocs = concatMap
  (\lhd -> case unLoc lhd of
    TyClD _ classDecl@ClassDecl{} ->
      concatMap
          (\(L _ decl, docs) ->
            map (, docs, getLocA lhd) $ getMainDeclBinder decl
          )
        $ classDeclDocs classDecl
    TyClD _ DataDecl {..} ->
      concatMap (\(L _ con) -> conDeclDocs con ++ selectorDocs con)
        $ dd_cons tcdDataDefn
    InstD _ (DataFamInstD _ DataFamInstDecl {..}) ->
      concatMap (conDeclDocs . unLoc) . dd_cons . feqn_rhs $ dfid_eqn
    _ -> []
  )


getMainDeclBinder :: HsDecl GhcRn -> [IdP GhcRn]
getMainDeclBinder (TyClD _ d) = [tcdName d]
getMainDeclBinder (ValD  _ d) = case collectHsBindBinders CollNoDictBinders d of
  []         -> []
  (name : _) -> [name]
getMainDeclBinder (SigD _ d) = sigNameNoLoc d
getMainDeclBinder (ForD _ (ForeignImport _ name _ _)) = [unLoc name]
getMainDeclBinder (ForD _ ForeignExport{}) = []
getMainDeclBinder _ = []

sigNameNoLoc :: forall p . UnXRec p => Sig p -> [IdP p]
sigNameNoLoc (TypeSig _ ns _             ) = map (unXRec @p) ns
sigNameNoLoc (ClassOpSig _ _ ns _        ) = map (unXRec @p) ns
sigNameNoLoc (PatSynSig _ ns _           ) = map (unXRec @p) ns
sigNameNoLoc (SpecSig _ n _ _            ) = [unXRec @p n]
sigNameNoLoc (InlineSig _ n _            ) = [unXRec @p n]
sigNameNoLoc (FixSig _ (FixitySig _ ns _)) = map (unXRec @p) ns
sigNameNoLoc _                             = []

clsInstDeclSrcSpan :: ClsInstDecl (GhcPass p) -> SrcSpan
clsInstDeclSrcSpan ClsInstDecl { cid_poly_ty = ty } = getLocA ty

hsDocsToDocH :: DynFlags -> GlobalRdrEnv -> [HsDocString] -> Doc Name
hsDocsToDocH flags rdrEnv =
  rename flags rdrEnv
    . overIdentifier (parseIdent flags)
    . _doc
    . parseParas Nothing
    . concatMap unpackHDS

parseIdent :: DynFlags -> Namespace -> String -> Maybe RdrName
parseIdent dflags _ str0 =
  let buffer    = stringToStringBuffer str0
      realSrcLc = mkRealSrcLoc (mkFastString "<unknown file>") 0 0
      pstate    = initParserState (initParserOpts dflags) buffer realSrcLc
  in  case unP parseIdentifier pstate of
        POk _ name -> Just (unLoc name)
        _          -> Nothing

type Doc id = DocH (ModuleName, OccName) id

rename :: DynFlags -> GlobalRdrEnv -> Doc RdrName -> Doc Name
rename dflags gre = rn
 where
  rn :: Doc RdrName -> Doc Name
  rn d = case d of
    DocAppend a b     -> DocAppend (rn a) (rn b)
    DocParagraph  doc -> DocParagraph (rn doc)
    DocIdentifier x   -> do
      -- Generate the choices for the possible kind of thing this
      -- is.
      let choices = dataTcOccs x
      -- Try to look up all the names in the GlobalRdrEnv that match
      -- the names.
      let names = concatMap
            (\c -> map grePrintableName (lookupGRE_RdrName c gre))
            choices

      case names of
        -- We found no names in the env so we start guessing.
        [] -> case choices of
          []    -> DocMonospaced (DocString (showPpr dflags x))
          -- There was nothing in the environment so we need to
          -- pick some default from what's available to us. We
          -- diverge here from the old way where we would default
          -- to type constructors as we're much more likely to
          -- actually want anchors to regular definitions than
          -- type constructor names (such as in #253). So now we
          -- only get type constructor links if they are actually
          -- in scope.
          a : _ -> outOfScope dflags a

        -- There is only one name in the environment that matches so
        -- use it.
        [a] -> DocIdentifier a
        -- But when there are multiple names available, default to
        -- type constructors: somewhat awfully GHC returns the
        -- values in the list positionally.
        a : b : _ | isTyConName a -> DocIdentifier a
                  | otherwise     -> DocIdentifier b

    DocWarning             doc       -> DocWarning (rn doc)
    DocEmphasis            doc       -> DocEmphasis (rn doc)
    DocBold                doc       -> DocBold (rn doc)
    DocMonospaced          doc       -> DocMonospaced (rn doc)
    DocUnorderedList       docs      -> DocUnorderedList (map rn docs)
    DocOrderedList         docs      -> DocOrderedList (map rn docs)
    DocDefList list -> DocDefList [ (rn a, rn b) | (a, b) <- list ]
    DocCodeBlock           doc       -> DocCodeBlock (rn doc)
    DocIdentifierUnchecked x         -> DocIdentifierUnchecked x
    DocModule              modLink   -> DocModule (rn <$> modLink)
    DocHyperlink           hyperLink -> DocHyperlink (rn <$> hyperLink)
    DocPic                 str       -> DocPic str
    DocMathInline          str       -> DocMathInline str
    DocMathDisplay         str       -> DocMathDisplay str
    DocAName               str       -> DocAName str
    DocProperty            p         -> DocProperty p
    DocExamples            e         -> DocExamples e
    DocEmpty                         -> DocEmpty
    DocString str                    -> DocString str
    DocHeader (Header l t)           -> DocHeader $ Header l (rn t)
    DocTable  t                      -> DocTable (rn <$> t)

-- | Wrap an identifier that's out of scope (i.e. wasn't found in
-- 'GlobalReaderEnv' during 'rename') in an appropriate doc. Currently
-- we simply monospace the identifier in most cases except when the
-- identifier is qualified: if the identifier is qualified then we can
-- still try to guess and generate anchors accross modules but the
-- users shouldn't rely on this doing the right thing. See tickets
-- #253 and #375 on the confusion this causes depending on which
-- default we pick in 'rename'.
outOfScope :: DynFlags -> RdrName -> Doc a
outOfScope dflags x = case x of
  Unqual occ   -> monospaced occ
  Qual mdl occ -> DocIdentifierUnchecked (mdl, occ)
  Orig _   occ -> monospaced occ
  Exact name   -> monospaced name -- Shouldn't happen since x is out of scope
 where
  monospaced :: (Outputable a) => a -> Doc b
  monospaced a = DocMonospaced (DocString (showPpr dflags a))

makeAnchorId :: String -> String
makeAnchorId []      = []
makeAnchorId (f : r) = escape isAlpha f ++ concatMap (escape isLegal) r
 where
  escape p c | p c       = [c]
             | otherwise = '-' : show (ord c) ++ "-"
  isLegal ':' = True
  isLegal '_' = True
  isLegal '.' = True
  isLegal c   = isAscii c && isAlphaNum c

ghcDL :: GHC.Located a -> GHC.Located a
ghcDL x = x