-- Copyright (c) 2020, Shayne Fletcher. All rights reserved.
-- SPDX-License-Identifier: BSD-3-Clause.

{-# LANGUAGE CPP #-}
#include "ghclib_api.h"

module Language.Haskell.GhclibParserEx.GHC.Types.Name.Reader(
   occNameStr, rdrNameStr, isSpecial, unqual, fromQual, isSymbolRdrName
 )
where

#if defined (GHCLIB_API_HEAD) || defined (GHCLIB_API_902)
import GHC.Parser.Annotation
#endif

#if defined (GHCLIB_API_HEAD) || defined(GHCLIB_API_902) || defined (GHCLIB_API_900)
import GHC.Types.SrcLoc
import GHC.Types.Name
import GHC.Types.Name.Reader
#else
import SrcLoc
import RdrName
import OccName
import Name
#endif

-- These names may not seem natural here but they work out in
-- practice. The use of thse two functions is thoroughly ubiquitous.
occNameStr :: RdrName -> String; occNameStr :: RdrName -> String
occNameStr = OccName -> String
occNameString (OccName -> String) -> (RdrName -> OccName) -> RdrName -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RdrName -> OccName
rdrNameOcc
#if defined (GHCLIB_API_HEAD) || defined (GHCLIB_API_902)
rdrNameStr :: GHC.Parser.Annotation.LocatedN RdrName -> String
#else
rdrNameStr :: Located RdrName -> String
#endif
rdrNameStr :: LocatedN RdrName -> String
rdrNameStr = RdrName -> String
occNameStr (RdrName -> String)
-> (LocatedN RdrName -> RdrName) -> LocatedN RdrName -> String
forall b c a. (b -> c) -> (a -> b) -> a -> c
. LocatedN RdrName -> RdrName
forall l e. GenLocated l e -> e
unLoc

-- Builtin type or data constructors.
#if defined (GHCLIB_API_HEAD) || defined (GHCLIB_API_902)
isSpecial :: LocatedN RdrName -> Bool
#else
isSpecial :: Located RdrName -> Bool
#endif
isSpecial :: LocatedN RdrName -> Bool
isSpecial (L SrcSpanAnnN
_ (Exact Name
n)) = Name -> Bool
isDataConName Name
n Bool -> Bool -> Bool
|| Name -> Bool
isTyConName Name
n
isSpecial LocatedN RdrName
_ = Bool
False

-- Coerce qualified names to unqualified (by discarding the
-- qualifier).
#if defined (GHCLIB_API_HEAD) || defined (GHCLIB_API_902)
unqual :: LocatedN RdrName -> LocatedN RdrName
#else
unqual :: Located RdrName -> Located RdrName
#endif
unqual :: LocatedN RdrName -> LocatedN RdrName
unqual (L SrcSpanAnnN
loc (Qual ModuleName
_ OccName
n)) = SrcSpanAnnN -> RdrName -> LocatedN RdrName
forall l e. l -> e -> GenLocated l e
L SrcSpanAnnN
loc (RdrName -> LocatedN RdrName) -> RdrName -> LocatedN RdrName
forall a b. (a -> b) -> a -> b
$ OccName -> RdrName
mkRdrUnqual OccName
n
unqual LocatedN RdrName
x = LocatedN RdrName
x

-- Extract the occ name from a qualified/unqualified reader name.
#if defined (GHCLIB_API_HEAD) || defined (GHCLIB_API_902)
fromQual :: LocatedN RdrName -> Maybe OccName
#else
fromQual :: Located RdrName -> Maybe OccName
#endif
fromQual :: LocatedN RdrName -> Maybe OccName
fromQual (L SrcSpanAnnN
_ (Qual ModuleName
_ OccName
x)) = OccName -> Maybe OccName
forall a. a -> Maybe a
Just OccName
x
fromQual (L SrcSpanAnnN
_ (Unqual OccName
x)) = OccName -> Maybe OccName
forall a. a -> Maybe a
Just OccName
x
fromQual LocatedN RdrName
_ = Maybe OccName
forall a. Maybe a
Nothing

-- Test if the reader name is that of an operator (be it a data
-- constructor, variable or whatever).
isSymbolRdrName :: RdrName -> Bool
isSymbolRdrName :: RdrName -> Bool
isSymbolRdrName = OccName -> Bool
isSymOcc (OccName -> Bool) -> (RdrName -> OccName) -> RdrName -> Bool
forall b c a. (b -> c) -> (a -> b) -> a -> c
. RdrName -> OccName
rdrNameOcc