#14539: untouchable type inside the constraints
-------------------------------------+-------------------------------------
Reporter: Lemming | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.2
(Type checker) |
Keywords: | Operating System: Unknown/Multiple
Architecture: | Type of failure: GHC rejects
Unknown/Multiple | valid program
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
-------------------------------------+-------------------------------------
The following code is taken and simplified from the test-suite of
`accelerate-fourier`:
{{{
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE Rank2Types #-}
module UntouchableType (tests) where
import Test.QuickCheck (Testable, Arbitrary, arbitrary, quickCheck, )
newtype Sign a = Sign a
deriving (Show)
instance Arbitrary (Sign a) where
arbitrary = undefined
quickCheckWithSign :: (Testable prop) => (Sign Double -> prop) -> IO ()
quickCheckWithSign = quickCheck
data Array sh a = Array
type family FullShape sh :: *
data SubTransform a =
SubTransform (forall sh. (FullShape sh ~ sh) => Array sh a)
transform2d :: SubTransform Double -> Bool
transform2d = undefined
transformChirp2 :: Sign a -> Array sh a
transformChirp2 = undefined
tests :: IO ()
tests =
quickCheck $ \sign ->
transform2d (SubTransform (transformChirp2 (sign::Sign Double)))
}}}
GHC-8.2.2 says about it:
{{{
[1 of 1] Compiling UntouchableType ( UntouchableType.hs, interpreted )
UntouchableType.hs:34:4: error:
• Ambiguous type variable ‘p0’ arising from a use of ‘quickCheck’
prevents the constraint ‘(Arbitrary p0)’ from being solved.
Probable fix: use a type annotation to specify what ‘p0’ should be.
These potential instances exist:
instance (Arbitrary a, Arbitrary b) => Arbitrary (Either a b)
-- Defined in ‘Test.QuickCheck.Arbitrary’
instance Arbitrary Ordering
-- Defined in ‘Test.QuickCheck.Arbitrary’
instance Arbitrary Integer
-- Defined in ‘Test.QuickCheck.Arbitrary’
...plus 20 others
...plus 62 instances involving out-of-scope types
(use -fprint-potential-instances to see them all)
• In the expression:
quickCheck
$ \ sign
-> transform2d
(SubTransform (transformChirp2 (sign :: Sign Double)))
In an equation for ‘tests’:
tests
= quickCheck
$ \ sign
-> transform2d
(SubTransform (transformChirp2 (sign :: Sign
Double)))
|
34 | quickCheck $ \sign ->
| ^^^^^^^^^^^^^^^^^^^^^...
UntouchableType.hs:35:51: error:
• Couldn't match expected type ‘Sign Double’ with actual type ‘p0’
‘p0’ is untouchable
inside the constraints: FullShape sh ~ sh
bound by a type expected by the context:
forall sh. FullShape sh ~ sh => Array sh Double
at UntouchableType.hs:35:20-69
• In the first argument of ‘transformChirp2’, namely
‘(sign :: Sign Double)’
In the first argument of ‘SubTransform’, namely
‘(transformChirp2 (sign :: Sign Double))’
In the first argument of ‘transform2d’, namely
‘(SubTransform (transformChirp2 (sign :: Sign Double)))’
• Relevant bindings include
sign :: p0 (bound at UntouchableType.hs:34:18)
|
35 | transform2d (SubTransform (transformChirp2 (sign::Sign
Double)))
| ^^^^
Failed, no modules loaded.
}}}
I have tested GHC versions back to GHC-7.4.2, all of them report
essentially the same type error.
I do not really understand the type error message, but here are my
observations that I find strange:
The type annotation `sign :: Sign Double` does not prevent the type error,
but replacing `quickCheck` by `quickCheckWithSign` does.
Replacing the constraint `FullShape sh ~ sh` by, e.g. `Show sh`, let the
error disappear.
Generalizing `transform2d` to `SubTransform a` causes another type error
although I expected that `SubTransform Double` can be infered from `Sign
Double`.
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14539>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
#14531: tcIfaceGlobal (local): not found
--------------------------------------+---------------------------------
Reporter: bigos | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.2.1
Keywords: Windows Msys2 | Operating System: Windows
Architecture: x86_64 (amd64) | Type of failure: None/Unknown
Test Case: | Blocked By:
Blocking: | Related Tickets:
Differential Rev(s): | Wiki Page:
--------------------------------------+---------------------------------
I have installed Msys2 on Windows. In Msys2 I have installed Emacs, which
I start with a custom cmd script with following environment variables set:
{{{
SET PATH=C:\msys64\mingw64\bin;C:\msys64\usr\bin;%PATH%
set XDG_DATA_DIRS=c:/msys64/mingw64/share
set PKG_CONFIG_PATH=c:/msys64/mingw64/lib/pkgconfig
set INCLUDE=c:/msys64/mingw64/include
}}}
The haskell I have is from Full Haskell Platform,
https://haskell.org/platform/download/8.2.1/HaskellPlatform-8.2.1-full-
x86_64-setup.exe
Then I started eshell which I used to invoke this command:
{{{
cabal install gi-gtk
}}}
Which after a while gave me following error.
{{{
[91 of 95] Compiling GI.Pango.Objects.Layout ( GI\Pango\Objects\Layout.hs,
dist\build\GI\Pango\Objects\Layout.o )
ghc.exe: panic! (the 'impossible' happened)
(GHC version 8.2.1 for x86_64-unknown-mingw32):
tcIfaceGlobal (local): not found
You are in a maze of twisty little passages, all alike.
While forcing the thunk for TyThing Layout
which was lazily initialized by initIfaceCheck typecheckLoop,
I tried to tie the knot, but I couldn't find Layout
in the current type environment.
If you are developing GHC, please read Note [Tying the knot]
and Note [Type-checking inside the knot].
Consider rebuilding GHC with profiling for a better stack trace.
Contents of current type environment: []
Call stack:
CallStack (from HasCallStack):
prettyCurrentCallStack, called at
compiler\utils\Outputable.hs:1133:58 in ghc:Outputable
callStackDoc, called at compiler\utils\Outputable.hs:1137:37 in
ghc:Outputable
pprPanic, called at compiler\iface\TcIface.hs:1696:23 in
ghc:TcIface
Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug
cabal: Leaving directory 'C:\Users\Jacek\AppData\Local\Temp\cabal-tmp-8093
\gi-pango-1.0.15'
Failed to install gi-gio-2.0.14
Build log ( C:\Users\Jacek\AppData\Roaming\cabal\logs\ghc-8.2.1\gi-
gio-2.0.14-GKluzGq73QJBrHtRklhQDd.log ):
Preprocessing library for gi-gio-2.0.14..
Building library for gi-gio-2.0.14..
}}}
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/14531>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler