Hassan Al-Awwadi pushed to branch wip/haanss/depdir at Glasgow Haskell Compiler / GHC
Commits:
-
668322d8
by Hassan Al-Awwadi at 2025-07-05T23:13:26+02:00
1 changed file:
Changes:
... | ... | @@ -1727,7 +1727,7 @@ module Language.Haskell.TH.Syntax where |
1727 | 1727 | qExtsEnabled :: m [Extension]
|
1728 | 1728 | qPutDoc :: DocLoc -> GHC.Internal.Base.String -> m ()
|
1729 | 1729 | qGetDoc :: DocLoc -> m (GHC.Internal.Maybe.Maybe GHC.Internal.Base.String)
|
1730 | - {-# MINIMAL qNewName, qReport, qRecover, qLookupName, qReify, qReifyFixity, qReifyType, qReifyInstances, qReifyRoles, qReifyAnnotations, qReifyModule, qReifyConStrictness, qLocation, qGetPackageRoot, qAddDependentFile, qAddTempFile, qAddTopDecls, qAddForeignFilePath, qAddModFinalizer, qAddCorePlugin, qGetQ, qPutQ, qIsExtEnabled, qExtsEnabled, qPutDoc, qGetDoc #-}
|
|
1730 | + {-# MINIMAL qNewName, qReport, qRecover, qLookupName, qReify, qReifyFixity, qReifyType, qReifyInstances, qReifyRoles, qReifyAnnotations, qReifyModule, qReifyConStrictness, qLocation, qGetPackageRoot, qAddDependentFile, qAddDependentDirectory, qAddTempFile, qAddTopDecls, qAddForeignFilePath, qAddModFinalizer, qAddCorePlugin, qGetQ, qPutQ, qIsExtEnabled, qExtsEnabled, qPutDoc, qGetDoc #-}
|
|
1731 | 1731 | type Quote :: (* -> *) -> Constraint
|
1732 | 1732 | class GHC.Internal.Base.Monad m => Quote m where
|
1733 | 1733 | newName :: GHC.Internal.Base.String -> m Name
|
... | ... | @@ -1781,6 +1781,7 @@ module Language.Haskell.TH.Syntax where |
1781 | 1781 | type VarStrictType = VarBangType
|
1782 | 1782 | addCorePlugin :: GHC.Internal.Base.String -> Q ()
|
1783 | 1783 | addDependentFile :: GHC.Internal.IO.FilePath -> Q ()
|
1784 | + addDependentDirectory :: GHC.Internal.IO.FilePath -> Q ()
|
|
1784 | 1785 | addForeignFile :: ForeignSrcLang -> GHC.Internal.Base.String -> Q ()
|
1785 | 1786 | addForeignFilePath :: ForeignSrcLang -> GHC.Internal.IO.FilePath -> Q ()
|
1786 | 1787 | addForeignSource :: ForeignSrcLang -> GHC.Internal.Base.String -> Q ()
|