diff --git a/compiler/iface/LoadIface.lhs b/compiler/iface/LoadIface.lhs
index a81b015..7f66fce 100644
--- a/compiler/iface/LoadIface.lhs
+++ b/compiler/iface/LoadIface.lhs
@@ -516,7 +516,11 @@ findAndReadIface doc_str mod hi_boot_file
 
        -- Check for GHC.Prim, and return its static interface
        if mod == gHC_PRIM
-           then return (Succeeded (ghcPrimIface,
+           then do
+               dflags <- getDynFlags
+               let iface = fromMaybe ghcPrimIface
+                               (sOverridePrimIface (settings dflags))
+               return (Succeeded (iface,
                                    "<built in interface for GHC.Prim>"))
            else do
                dflags <- getDynFlags
diff --git a/compiler/main/DynFlags.hs b/compiler/main/DynFlags.hs
index 1f39903..1101c55 100644
--- a/compiler/main/DynFlags.hs
+++ b/compiler/main/DynFlags.hs
@@ -149,6 +149,7 @@ import Outputable
 import Foreign.C        ( CInt(..) )
 #endif
 import {-# SOURCE #-} ErrUtils ( Severity(..), MsgDoc, mkLocMessage )
+import {-# SOURCE #-} HscTypes ( ModIface )
 
 import System.IO.Unsafe ( unsafePerformIO )
 import Data.IORef
@@ -768,7 +769,8 @@ data Settings = Settings {
   sOpt_lo                :: [String], -- LLVM: llvm optimiser
   sOpt_lc                :: [String], -- LLVM: llc static compiler
 
-  sPlatformConstants     :: PlatformConstants
+  sPlatformConstants     :: PlatformConstants,
+  sOverridePrimIface     :: Maybe ModIface
  }
 
 targetPlatform :: DynFlags -> Platform
diff --git a/compiler/main/HscTypes.lhs-boot b/compiler/main/HscTypes.lhs-boot
new file mode 100644
index 0000000..cf68e73
--- /dev/null
+++ b/compiler/main/HscTypes.lhs-boot
@@ -0,0 +1,7 @@
+\begin{code}
+
+module HscTypes where
+
+data ModIface
+
+\end{code}
diff --git a/compiler/main/SysTools.lhs b/compiler/main/SysTools.lhs
index 40a7a25..a17c4a8 100644
--- a/compiler/main/SysTools.lhs
+++ b/compiler/main/SysTools.lhs
@@ -339,7 +339,8 @@ initSysTools mbMinusB
                     sOpt_windres = [],
                     sOpt_lo      = [],
                     sOpt_lc      = [],
-                    sPlatformConstants = platformConstants
+                    sPlatformConstants = platformConstants,
+                    sOverridePrimIface = Nothing
              }
 \end{code}
 
