{-# LANGUAGE CPP #-}
-- Copyright 2019 Google LLC
--
-- Use of this source code is governed by a BSD-style
-- license that can be found in the LICENSE file or at
-- https://developers.google.com/open-source/licenses/bsd

-- | This module provides combinators for constructing Haskell modules,
-- including import and export statements.
module GHC.SourceGen.Module
    ( -- * HsModule'
      HsModule'
    , module'
      -- * Import declarations
    , ImportDecl'
    , qualified'
    , as'
    , import'
    , exposing
    , hiding
    , source
      -- * Imported/exported things
    , IE'
    , thingAll
    , thingWith
    , moduleContents
    )  where

import GHC.Hs.ImpExp
    ( IEWildcard(..), IEWrappedName(..), IE(..)
#if MIN_VERSION_ghc(9,6,0)
    , ImportListInterpretation (EverythingBut, Exactly), XImportDeclPass (ideclSourceText, ideclImplicit)
#else
    , LIEWrappedName
#endif
    )
import GHC.Hs
    ( HsModule(..)
    , ImportDecl(..)
#if MIN_VERSION_ghc(8,10,0)
    , ImportDeclQualifiedStyle(..)
#endif
#if MIN_VERSION_ghc(9,2,0)
    , EpAnn(..)
#endif
#if MIN_VERSION_ghc(9,6,0)
    , hsmodDeprecMessage, hsmodHaddockModHeader, hsmodAnn, AnnKeywordId, XModulePs (XModulePs, hsmodLayout), noAnn, LayoutInfo (NoLayoutInfo), GhcPs, XImportDeclPass (XImportDeclPass, ideclAnn), SrcSpanAnnA, noExtField
#endif
    )
#if MIN_VERSION_ghc(9,0,0) && !MIN_VERSION_ghc(9,6,0)
import GHC.Types.SrcLoc (LayoutInfo(..))
#endif
#if MIN_VERSION_ghc(9,0,0)
import GHC.Unit.Module (IsBootInterface(..))
import GHC.Types.Name.Reader (RdrName)
#else
import RdrName (RdrName)
#endif
#if MIN_VERSION_ghc(9,4,0)
import GHC.Types.PkgQual (RawPkgQual(..))
#endif

import GHC.SourceGen.Syntax.Internal
import GHC.SourceGen.Name.Internal
import GHC.SourceGen.Lit.Internal (noSourceText)
#if MIN_VERSION_ghc(9,0,0)
import GHC.SourceGen.Name (unqual)
#endif
#if MIN_VERSION_ghc(9,4,0)
import GHC.SourceGen.Name (RdrNameStr, ModuleNameStr(unModuleNameStr), OccNameStr)
import GHC.Types.SourceText (SourceText(NoSourceText))
import GHC.Types.SrcLoc (GenLocated)
#endif

module'
    :: Maybe ModuleNameStr
    -> Maybe [IE'] -- ^ Exports
    -> [ImportDecl']
    -> [HsDecl']
    -> HsModule'
module' :: Maybe ModuleNameStr
-> Maybe [IE'] -> [ImportDecl'] -> [HsDecl'] -> HsModule'
module' Maybe ModuleNameStr
name Maybe [IE']
exports [ImportDecl']
imports [HsDecl']
decls = HsModule
    { hsmodName :: Maybe (LocatedA ModuleName)
hsmodName = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a ann. a -> GenLocated (SrcSpanAnn ann) a
mkLocated forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModuleNameStr -> ModuleName
unModuleNameStr) Maybe ModuleNameStr
name
    , hsmodExports :: Maybe (LocatedL [LIE GhcPs])
hsmodExports = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap (forall a ann. a -> GenLocated (SrcSpanAnn ann) a
mkLocated forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a b. (a -> b) -> [a] -> [b]
map forall a ann. a -> GenLocated (SrcSpanAnn ann) a
mkLocated) Maybe [IE']
exports
    , hsmodImports :: [LImportDecl GhcPs]
hsmodImports = forall a b. (a -> b) -> [a] -> [b]
map forall a ann. a -> GenLocated (SrcSpanAnn ann) a
mkLocated [ImportDecl']
imports
    , hsmodDecls :: [LHsDecl GhcPs]
hsmodDecls = forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
fmap forall a ann. a -> GenLocated (SrcSpanAnn ann) a
mkLocated [HsDecl']
decls
#if MIN_VERSION_ghc(9,6,0)
    , hsmodExt = XModulePs
      { hsmodAnn = noAnn
      , hsmodLayout = NoLayoutInfo
      , hsmodDeprecMessage = Nothing
      , hsmodHaddockModHeader = Nothing }
#else
    , hsmodDeprecMessage :: Maybe (LocatedP WarningTxt)
hsmodDeprecMessage = forall a. Maybe a
Nothing
    , hsmodHaddockModHeader :: Maybe LHsDocString
hsmodHaddockModHeader = forall a. Maybe a
Nothing
#  if MIN_VERSION_ghc(9,0,0)
    , hsmodLayout :: LayoutInfo
hsmodLayout = LayoutInfo
NoLayoutInfo
#  endif
#  if MIN_VERSION_ghc(9,2,0)
    , hsmodAnn :: EpAnn AnnsModule
hsmodAnn = forall ann. EpAnn ann
EpAnnNotUsed
#  endif
#endif
    }

qualified' :: ImportDecl' -> ImportDecl'
qualified' :: ImportDecl' -> ImportDecl'
qualified' ImportDecl'
d = ImportDecl'
d { ideclQualified :: ImportDeclQualifiedStyle
ideclQualified =
#if MIN_VERSION_ghc(8,10,0)
    ImportDeclQualifiedStyle
QualifiedPre
#else
    True
#endif
}

as' :: ImportDecl' -> ModuleNameStr -> ImportDecl'
as' :: ImportDecl' -> ModuleNameStr -> ImportDecl'
as' ImportDecl'
d ModuleNameStr
m = ImportDecl'
d { ideclAs :: Maybe (XRec GhcPs ModuleName)
ideclAs = forall a. a -> Maybe a
Just (forall a ann. a -> GenLocated (SrcSpanAnn ann) a
mkLocated forall a b. (a -> b) -> a -> b
$ ModuleNameStr -> ModuleName
unModuleNameStr ModuleNameStr
m) }

import' :: ModuleNameStr -> ImportDecl'
import' :: ModuleNameStr -> ImportDecl'
import' ModuleNameStr
m = XRec GhcPs ModuleName
-> Maybe StringLiteral
-> IsBootInterface
-> Bool
-> ImportDeclQualifiedStyle
-> Bool
-> Maybe (XRec GhcPs ModuleName)
-> Maybe (Bool, XRec GhcPs [LIE GhcPs])
-> ImportDecl'
importDecl
            (forall a ann. a -> GenLocated (SrcSpanAnn ann) a
mkLocated forall a b. (a -> b) -> a -> b
$ ModuleNameStr -> ModuleName
unModuleNameStr ModuleNameStr
m)
#if MIN_VERSION_ghc(9,4,0)
            NoRawPkgQual
#else
            forall a. Maybe a
Nothing
#endif
#if MIN_VERSION_ghc(9,0,0)
            IsBootInterface
NotBoot
#else
            False
#endif
            Bool
False
#if MIN_VERSION_ghc(8,10,0)
            ImportDeclQualifiedStyle
NotQualified
#else
            False
#endif
#if !MIN_VERSION_ghc(9,6,0)
            Bool
False
#endif
            forall a. Maybe a
Nothing forall a. Maybe a
Nothing
  where
#if MIN_VERSION_ghc(9,6,0)
    importDecl = ImportDecl
            (XImportDeclPass{ ideclAnn = EpAnnNotUsed
            , ideclSourceText = NoSourceText
            , ideclImplicit = False
             })
#else
    importDecl :: XRec GhcPs ModuleName
-> Maybe StringLiteral
-> IsBootInterface
-> Bool
-> ImportDeclQualifiedStyle
-> Bool
-> Maybe (XRec GhcPs ModuleName)
-> Maybe (Bool, XRec GhcPs [LIE GhcPs])
-> ImportDecl'
importDecl = forall a. (SourceText -> a) -> a
noSourceText (forall ann a. (EpAnn ann -> a) -> a
withEpAnnNotUsed forall pass.
XCImportDecl pass
-> SourceText
-> XRec pass ModuleName
-> Maybe StringLiteral
-> IsBootInterface
-> Bool
-> ImportDeclQualifiedStyle
-> Bool
-> Maybe (XRec pass ModuleName)
-> Maybe (Bool, XRec pass [LIE pass])
-> ImportDecl pass
ImportDecl)
#endif

exposing :: ImportDecl' -> [IE'] -> ImportDecl'
exposing :: ImportDecl' -> [IE'] -> ImportDecl'
exposing ImportDecl'
d [IE']
ies = ImportDecl'
d
#if MIN_VERSION_ghc(9,6,0)
    { ideclImportList = Just (Exactly, mkLocated $ map mkLocated ies) }
#else
    { ideclHiding :: Maybe (Bool, XRec GhcPs [LIE GhcPs])
ideclHiding = forall a. a -> Maybe a
Just (Bool
False, forall a ann. a -> GenLocated (SrcSpanAnn ann) a
mkLocated forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a ann. a -> GenLocated (SrcSpanAnn ann) a
mkLocated [IE']
ies) }
#endif

hiding :: ImportDecl' -> [IE'] -> ImportDecl'
hiding :: ImportDecl' -> [IE'] -> ImportDecl'
hiding ImportDecl'
d [IE']
ies = ImportDecl'
d
#if MIN_VERSION_ghc(9,6,0)
    { ideclImportList = Just (EverythingBut, mkLocated $ map mkLocated ies) }
#else
    { ideclHiding :: Maybe (Bool, XRec GhcPs [LIE GhcPs])
ideclHiding = forall a. a -> Maybe a
Just (Bool
True, forall a ann. a -> GenLocated (SrcSpanAnn ann) a
mkLocated forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall a ann. a -> GenLocated (SrcSpanAnn ann) a
mkLocated [IE']
ies) }
#endif

-- | Adds the @{-# SOURCE #-}@ pragma to an import.
source :: ImportDecl' -> ImportDecl'
source :: ImportDecl' -> ImportDecl'
source ImportDecl'
d = ImportDecl'
d { ideclSource :: IsBootInterface
ideclSource =
#if MIN_VERSION_ghc(9,0,0)
    IsBootInterface
IsBoot
#else
    True
#endif
}

-- | Exports all methods and/or constructors.
--
-- > A(..)
-- > =====
-- > thingAll "A"
thingAll :: RdrNameStr -> IE'
thingAll :: RdrNameStr -> IE'
thingAll = forall ann a. (EpAnn ann -> a) -> a
withEpAnnNotUsed forall pass.
XIEThingAll pass -> LIEWrappedName (IdP pass) -> IE pass
IEThingAll forall b c a. (b -> c) -> (a -> b) -> a -> c
. RdrNameStr -> LIEWrappedName RdrName
wrappedName

-- | Exports specific methods and/or constructors.
--
-- > A(b, C)
-- > =====
-- > thingWith "A" ["b", "C"]
thingWith :: RdrNameStr -> [OccNameStr] -> IE'
thingWith :: RdrNameStr -> [OccNameStr] -> IE'
thingWith RdrNameStr
n [OccNameStr]
cs = forall ann a. (EpAnn ann -> a) -> a
withEpAnnNotUsed forall pass.
XIEThingWith pass
-> LIEWrappedName (IdP pass)
-> IEWildcard
-> [LIEWrappedName (IdP pass)]
-> IE pass
IEThingWith (RdrNameStr -> LIEWrappedName RdrName
wrappedName RdrNameStr
n) IEWildcard
NoIEWildcard
                    (forall a b. (a -> b) -> [a] -> [b]
map (RdrNameStr -> LIEWrappedName RdrName
wrappedName forall b c a. (b -> c) -> (a -> b) -> a -> c
. OccNameStr -> RdrNameStr
unqual) [OccNameStr]
cs)
#if !MIN_VERSION_ghc(9,2,0)
                    -- The parsing step leaves the list of fields empty
                    -- and lumps them all together with the above list of
                    -- constructors.
                    []
#endif

-- TODO: support "mixed" syntax with both ".." and explicit names.

#if MIN_VERSION_ghc(9,6,0)
wrappedName :: RdrNameStr -> GenLocated SrcSpanAnnA (IEWrappedName GhcPs)
wrappedName rNameStr = mkLocated (IEName noExtField $ exportRdrName rNameStr)
#else
wrappedName :: RdrNameStr -> LIEWrappedName RdrName
wrappedName :: RdrNameStr -> LIEWrappedName RdrName
wrappedName = forall a ann. a -> GenLocated (SrcSpanAnn ann) a
mkLocated forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall name. LocatedN name -> IEWrappedName name
IEName forall b c a. (b -> c) -> (a -> b) -> a -> c
. RdrNameStr -> LocatedN RdrName
exportRdrName
#endif

-- | Exports an entire module.
--
-- Note: this is not valid inside of an import list.
--
-- > module M
-- > =====
-- > moduleContents "M"
moduleContents :: ModuleNameStr -> IE'
moduleContents :: ModuleNameStr -> IE'
moduleContents = forall ann a. (EpAnn ann -> a) -> a
withEpAnnNotUsed forall pass.
XIEModuleContents pass -> XRec pass ModuleName -> IE pass
IEModuleContents forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall a ann. a -> GenLocated (SrcSpanAnn ann) a
mkLocated forall b c a. (b -> c) -> (a -> b) -> a -> c
. ModuleNameStr -> ModuleName
unModuleNameStr