Skip to content

Commit

Permalink
Compatibility with ghc 9.10
Browse files Browse the repository at this point in the history
This is primarily useful for building the boot libraries.

When building with `ghc-internals` for 9.10, we do not support `seq#`.
  • Loading branch information
edsko committed Jan 12, 2025
1 parent 6cda4c4 commit 4416b54
Show file tree
Hide file tree
Showing 10 changed files with 241 additions and 126 deletions.
5 changes: 5 additions & 0 deletions .github/workflows/haskell-ci.yml
Original file line number Diff line number Diff line change
Expand Up @@ -33,6 +33,11 @@ jobs:
compilerVersion: 9.12.1
setup-method: ghcup
allow-failure: false
- compiler: ghc-9.10.1
compilerKind: ghc
compilerVersion: 9.10.1
setup-method: ghcup
allow-failure: false
fail-fast: false
steps:
- name: apt-get install
Expand Down
3 changes: 2 additions & 1 deletion README.md
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,8 @@ processing the event log yourself or by using
## Limitations and future work
* Requires GHC 9.12
* Requires GHC 9.10 or 9.12
(profiling of _pure_ foreign imports requires ghc 9.12).
* Standard time profiling tools can _NOT_ be used on the eventlog.
* It is not possible to profile Haskell functions and FFI functions at the
same time.
Expand Down
6 changes: 3 additions & 3 deletions example-pkg-A/example-pkg-A.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -12,14 +12,14 @@ category: Development
build-type: Simple
extra-source-files: cbits/cbits.h
cbits/cbits.c
tested-with: GHC ==9.12.1
tested-with: GHC ==9.10.1
GHC ==9.12.1

common lang
ghc-options:
-Wall
build-depends:
-- For now we don't support ghc < 9.12
base >= 4.21 && < 4.22
base >= 4.20 && < 4.22
default-language:
GHC2021

Expand Down
6 changes: 3 additions & 3 deletions example-pkg-B/example-pkg-B.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -12,14 +12,14 @@ author: Edsko de Vries
maintainer: [email protected]
category: Development
build-type: Simple
tested-with: GHC ==9.12.1
tested-with: GHC ==9.10.1
GHC ==9.12.1

common lang
ghc-options:
-Wall
build-depends:
-- For now we don't support ghc < 9.12
base >= 4.21 && < 4.22
base >= 4.20 && < 4.22
default-language:
GHC2021

Expand Down
124 changes: 23 additions & 101 deletions trace-foreign-calls/src/Plugin/TraceForeignCalls.hs
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE ViewPatterns #-}

{-# OPTIONS_GHC -Wno-incomplete-uni-patterns #-}

module Plugin.TraceForeignCalls (plugin) where
Expand All @@ -20,17 +21,20 @@ import GHC.Tc.Utils.Monad qualified as TC
import GHC.Types.ForeignCall qualified as Foreign
import GHC.Types.SourceFile (isHsBootOrSig)

import Plugin.TraceForeignCalls.GHC.Shim
import Plugin.TraceForeignCalls.GHC.Util
import Plugin.TraceForeignCalls.Instrument
import Plugin.TraceForeignCalls.Options
import Plugin.TraceForeignCalls.Util.GHC

{-------------------------------------------------------------------------------
Top-level
References:
- https://downloads.haskell.org/ghc/9.12.1/docs/users_guide/extending_ghc.html#compiler-plugins
- https://hackage.haskell.org/package/ghc-9.10.1
- https://hackage.haskell.org/package/ghc-9.12.1
- https://downloads.haskell.org/ghc/9.12.1/docs/users_guide/extending_ghc.html#compiler-plugins
- https://downloads.haskell.org/ghc/9.12.1/docs/users_guide/exts/ffi.html
- https://www.haskell.org/onlinereport/haskell2010/haskellch8.html
-------------------------------------------------------------------------------}
Expand Down Expand Up @@ -69,7 +73,7 @@ processRenamed options tcGblEnv group
processGroup :: HsGroup GhcRn -> Instrument (HsGroup GhcRn)
processGroup group@HsGroup{
hs_fords
, hs_valds = XValBindsLR (NValBinds bindingGroups sigs)
, hs_valds = existingBindings
} = do
mTraceCCS <- findName nameTraceCCS

Expand All @@ -90,13 +94,11 @@ processGroup group@HsGroup{
, map reconstructForeignDecl imports
]
, hs_valds =
XValBindsLR $
NValBinds
(map trivialBindingGroup newValues ++ bindingGroups)
( newSigs ++ sigs )
extendValBinds
(map trivialBindingGroup newValues)
newSigs
existingBindings
}
processGroup HsGroup{hs_valds = ValBinds{}} =
error "impossible (ValBinds is only used before renaming)"

{-------------------------------------------------------------------------------
Foreign declarations
Expand Down Expand Up @@ -256,7 +258,6 @@ renameForeignImport (L l n) = do
mkWrapper :: ReplacedForeignImport -> Instrument (LSig GhcRn, LHsBind GhcRn)
mkWrapper rfi@ReplacedForeignImport {
rfiOriginalName
, rfiSuffixedName
, rfiSigType = L _ sigType
} = do
(args, body) <- mkWrapperBody rfi
Expand All @@ -272,36 +273,7 @@ mkWrapper rfi@ReplacedForeignImport {
sig_body = sig_body sigType
}
}
, noLocValue $
FunBind {
fun_ext = mkNameSet [unLoc rfiSuffixedName]
, fun_id = rfiOriginalName
, fun_matches = MG {
mg_ext = Generated OtherExpansion SkipPmc
, mg_alts = noLocValue . map noLocValue $ [
Match {
m_ext = noValue
, m_ctxt = FunRhs {
mc_fun = rfiOriginalName
, mc_fixity = Prefix
, mc_strictness = NoSrcStrict
, mc_an = AnnFunRhs NoEpTok [] []
}
, m_pats = noLocValue $ map namedVarPat args
, m_grhss = GRHSs {
grhssExt = emptyComments
, grhssGRHSs = map noLocValue [
GRHS
noValue
[] -- guards
body
]
, grhssLocalBinds = emptyWhereClause
}
}
]
}
}
, mkSimpleFunBind rfiOriginalName [] args body
)

-- | Make the body for the wrapper
Expand Down Expand Up @@ -436,12 +408,9 @@ mkEventLogReturn ReplacedForeignImport{rfiOriginalName} =
]

{-------------------------------------------------------------------------------
Auxiliary
Auxiliary: constructions with fresh names
-------------------------------------------------------------------------------}

trivialBindingGroup :: LHsBind GhcRn -> (RecFlag, [LHsBind GhcRn])
trivialBindingGroup binding = (NonRecursive, [binding])

-- | Create unique name for each argument of the function
uniqArgsFor :: LHsType GhcRn -> Instrument [Name]
uniqArgsFor = go [] . unLoc
Expand All @@ -455,57 +424,6 @@ uniqArgsFor = go [] . unLoc
go acc _otherTy =
return $ reverse acc

-- | Check if a function signature returns something in the @IO@ monad
checkIsIO :: LHsSigType GhcRn -> Bool
checkIsIO = go . unLoc . sig_body . unLoc
where
go :: HsType GhcRn -> Bool
go HsForAllTy{hst_body} = go (unLoc hst_body)
go HsQualTy{hst_body} = go (unLoc hst_body)
go (HsFunTy _ _ _ rhs) = go (unLoc rhs)
go ty =
case ty of
HsAppTy _ (L _ (HsTyVar _ _ (L _ io))) _ | io == Names.ioTyConName ->
True
_otherwise ->
False

emptyWhereClause :: HsLocalBinds GhcRn
emptyWhereClause = EmptyLocalBinds noValue

ubstringExpr :: String -> LHsExpr GhcRn
ubstringExpr = noLocValue . HsLit noValue . mkHsStringPrimLit . fsLit

callLNamedFn :: LIdP GhcRn -> [LHsExpr GhcRn] -> LHsExpr GhcRn
callLNamedFn fn args =
mkHsApps (noLocValue $ HsVar noValue fn) $
map mkLHsPar args

callNamedFn :: IdP GhcRn -> [LHsExpr GhcRn] -> LHsExpr GhcRn
callNamedFn = callLNamedFn . noLocValue

namedLVar :: LIdP GhcRn -> LHsExpr GhcRn
namedLVar = noLocValue . HsVar noValue

namedVar :: IdP GhcRn -> LHsExpr GhcRn
namedVar = namedLVar . noLocValue

namedVarPat :: Name -> LPat GhcRn
namedVarPat = noLocValue . VarPat noValue . noLocValue

-- | @IO ()@
ioUnit :: LHsType GhcRn
ioUnit =
nlHsAppTy
(nlHsTyVar NotPromoted Names.ioTyConName)
(nlHsTyVar NotPromoted (tyConName unitTyCon))

{-------------------------------------------------------------------------------
Auxiliary: construct IO calls
-------------------------------------------------------------------------------}

type RealWorld = LHsExpr GhcRn

-- | Bind to value without evaluating it
--
-- Given @e@, constructs
Expand Down Expand Up @@ -534,11 +452,16 @@ let_ xNameHint e k = do
}
return $ noLocValue $
HsLet noValue (
HsValBinds noValue $
XValBindsLR $ NValBinds [(NonRecursive, [binding])] []
HsValBinds noValue $ mkValBinds [(NonRecursive, [binding])] []
)
$ cont

{-------------------------------------------------------------------------------
Auxiliary: construct IO calls
-------------------------------------------------------------------------------}

type RealWorld = LHsExpr GhcRn

-- | Unwrap @IO@ action
--
-- Given @io@ and continuation @k@, constructs
Expand Down Expand Up @@ -580,7 +503,7 @@ wrapIO f = do
body <- f (namedVar s)
return $
mkHsApp (namedVar Names.ioDataConName)
$ mkHsLam (noLocValue [namedVarPat s])
$ mkLambda [namedVarPat s]
$ body

-- | Similar to 'wrapIO', but in a pure context (essentially @unsafePerformIO@)
Expand All @@ -599,7 +522,7 @@ runIO f = do
runRW <- findName nameRunRW
noDup <- findName nameNoDuplicate
body <- f $ callNamedFn noDup [namedVar s]
let scrut = callNamedFn runRW [mkHsLam (noLocValue [namedVarPat s]) body]
let scrut = callNamedFn runRW [mkLambda [namedVarPat s] body]
return $ noLocValue $
HsCase CaseAlt scrut
$ mkMatchGroup (Generated OtherExpansion SkipPmc) . noLocValue . pure
Expand Down Expand Up @@ -728,4 +651,3 @@ callNamedIO f args s = do
fName <- findName f
return $ callNamedFn fName (args ++ [s])


Loading

0 comments on commit 4416b54

Please sign in to comment.