Build failure on PowerPC 64-bit big endian
Building GHC 8.6.1 alpha 2 fails with these errors on Powerpc 64-bit big endian Linux:
[ 5076s] utils/check-ppr/Main.hs:44:18: error:
[ 5076s] * GHC internal error: `astFile' is not in scope during type checking, but it passed the renamer
[ 5076s] tcl_env of environment: [agVj :-> Identifier[libdir::FilePath, NotLetBound],
[ 5076s] agVk :-> Identifier[fileName::String, NotLetBound],
[ 5076s] agVl :-> Identifier[p::a, NotLetBound],
[ 5076s] agVo :-> Identifier[anns::ApiAnns, TopLevelLet [agVl :-> p] False],
[ 5076s] agVp :-> Identifier[pragmas::String, TopLevelLet [agVo :-> anns] False],
[ 5076s] agVq :-> Identifier[newFile::FilePath, TopLevelLet [agVk :-> fileName] False],
[ 5076s] rfRp :-> Identifier[usage::String, TopLevelLet [] True],
[ 5076s] rfU1 :-> Identifier[main::IO (), TopLevelLet [] True],
[ 5076s] rfU2 :-> Identifier[testOneFile::FilePath
[ 5076s] -> String
[ 5076s] -> IO (), TopLevelLet [] True],
[ 5076s] rfU3 :-> Identifier[parseOneFile::FilePath
[ 5076s] -> FilePath
[ 5076s] -> IO
[ 5076s] ParsedModule, TopLevelLet [] True],
[ 5076s] rfU4 :-> Identifier[getPragmas::ApiAnns -> String, TopLevelLet],
[ 5076s] rfU5 :-> Identifier[pp::forall a.
[ 5076s] Outputable a =>
[ 5076s] a -> String, TopLevelLet [] True]]
[ 5076s] * In the first argument of `writeFile', namely `astFile'
[ 5076s] In a stmt of a 'do' block: writeFile astFile origAst
[ 5076s] In the expression:
[ 5076s] do p <- parseOneFile libdir fileName
[ 5076s] let pped = pragmas ++ "\n" ++ pp (pm_parsed_source p)
[ 5076s] anns = pm_annotations p
[ 5076s] ....
[ 5076s] writeFile astFile origAst
[ 5076s] writeFile newFile pped
[ 5076s] ....
[ 5076s] |
[ 5076s] 44 | writeFile astFile origAst
[ 5076s] | ^^^^^^^
[ 5076s] utils/check-ppr/ghc.mk:18: recipe for target 'utils/check-ppr/dist-install/build/Main.o' failed
[ 5076s] make[1]: *** [utils/check-ppr/dist-install/build/Main.o] Error 1
[ 5076s] make[1]: *** Waiting for unfinished jobs....
[ 5077s]
[ 5077s] utils/check-api-annotations/Main.hs:116:32: error:
[ 5077s] * GHC internal error: `GenericQ' is not in scope during type checking, but it passed the renamer
[ 5077s] tcl_env of environment: [agZx :-> Type variable `r' = r :: k0]
[ 5077s] * In the type signature:
[ 5077s] everything :: (r -> r -> r) -> GenericQ r -> GenericQ r
[ 5077s] |
[ 5077s] 116 | everything :: (r -> r -> r) -> GenericQ r -> GenericQ r
[ 5077s] | ^^^^^^^^
[ 5077s] utils/check-api-annotations/ghc.mk:18: recipe for target 'utils/check-api-annotations/dist-install/build/Main.o' failed
[ 5077s] make[1]: *** [utils/check-api-annotations/dist-install/build/Main.o] Error 1
[ 5077s]
[ 5077s] utils/ghctags/Main.hs:61:36: error:
[ 5077s] * GHC internal error: `FoundThing' is not in scope during type checking, but it passed the renamer
[ 5077s] tcl_env of environment: [rCTr :-> ATcTyCon FileData :: *,
[ 5077s] rCTs :-> APromotionErr RecDataConPE,
[ 5077s] rCTw :-> ATcTyCon FileName :: *]
[ 5077s] * In the type `[FoundThing]'
[ 5077s] In the definition of data constructor `FileData'
[ 5077s] In the data declaration for `FileData'
[ 5077s] |
[ 5077s] 61 | data FileData = FileData FileName [FoundThing] (Map Int String)
[ 5077s] | ^^^^^^^^^^
[ 5077s] utils/ghctags/ghc.mk:18: recipe for target 'utils/ghctags/dist-install/build/Main.o' failed
Alpha 2 builds fine on PowerPC 64-bit little endian Linux.
I am setting version to 8.5 as there is no tag for 8.6.1 alpha 2 yet.
Trac metadata
Trac field | Value |
---|---|
Version | 8.5 |
Type | Bug |
TypeOfFailure | OtherFailure |
Priority | normal |
Resolution | Unresolved |
Component | Compiler |
Test case | |
Differential revisions | |
BlockedBy | |
Related | |
Blocking | |
CC | |
Operating system | |
Architecture |