Skip to content
Snippets Groups Projects
Unverified Commit feca3a07 authored by Rodrigo Mesquita's avatar Rodrigo Mesquita :seedling:
Browse files

Disable optimisations in CabalHooks haskell-gi

Because of GHC potential bug being triggered by optimisations...
parent 0f4ba963
No related branches found
No related tags found
1 merge request!25Use cabal-version 3.14
......@@ -43,12 +43,15 @@ index 7f863e8..8930a5a 100644
containers,
directory,
diff --git a/lib/Data/GI/CodeGen/CabalHooks.hs b/lib/Data/GI/CodeGen/CabalHooks.hs
index 23735c2..c1d76f6 100644
index 23735c2..097c605 100644
--- a/lib/Data/GI/CodeGen/CabalHooks.hs
+++ b/lib/Data/GI/CodeGen/CabalHooks.hs
@@ -1,17 +1,28 @@
@@ -1,17 +1,31 @@
-- | Convenience hooks for writing custom @Setup.hs@ files for
-- bindings.
+{-# OPTIONS_GHC -O0 #-}
+-- \^ Unfortunately, it seems there is a GHC bug related to static pointers
+-- triggered by this program, so we compile without optimisations to workaround it.
+{-# LANGUAGE DerivingStrategies #-}
+{-# LANGUAGE DeriveAnyClass #-}
+{-# LANGUAGE DeriveGeneric #-}
......@@ -80,7 +83,7 @@ index 23735c2..c1d76f6 100644
import Data.GI.CodeGen.API (loadGIRInfo)
import Data.GI.CodeGen.Code (genCode, writeModuleTree, listModuleTree,
@@ -27,9 +38,10 @@ import Data.GI.CodeGen.Util (utf8ReadFile, utf8WriteFile, ucFirst)
@@ -27,9 +41,10 @@ import Data.GI.CodeGen.Util (utf8ReadFile, utf8WriteFile, ucFirst)
import System.Directory (createDirectoryIfMissing)
import System.FilePath (joinPath, takeDirectory)
......@@ -93,7 +96,7 @@ index 23735c2..c1d76f6 100644
import qualified Data.Map as M
#if !MIN_VERSION_base(4,11,0)
import Data.Monoid ((<>))
@@ -37,9 +49,8 @@ import Data.Monoid ((<>))
@@ -37,9 +52,8 @@ import Data.Monoid ((<>))
import qualified Data.Set as S
import Data.Text (Text)
import qualified Data.Text as T
......@@ -105,7 +108,7 @@ index 23735c2..c1d76f6 100644
-- | Included overrides file.
data TaggedOverride =
@@ -47,6 +58,8 @@ data TaggedOverride =
@@ -47,6 +61,8 @@ data TaggedOverride =
-- ^ Tag for the override, for error reporting purposes.
, overrideText :: Text
}
......@@ -114,7 +117,7 @@ index 23735c2..c1d76f6 100644
-- | Generate the code for the given module.
genModuleCode :: Text -- ^ name
@@ -111,66 +124,108 @@ genConfigModule outputDir modName maybeGiven = do
@@ -111,66 +127,108 @@ genConfigModule outputDir modName maybeGiven = do
quoteOverrides (Just (TaggedOverride _ ovText)) =
map (T.pack . show) (T.lines ovText)
......
0% Loading or .
You are about to add 0 people to the discussion. Proceed with caution.
Finish editing this message first!
Please register or to comment