diff options
author | Simon Peyton Jones <simonpj@microsoft.com> | 2018-01-31 13:05:13 +0000 |
---|---|---|
committer | Simon Peyton Jones <simonpj@microsoft.com> | 2018-01-31 13:24:23 +0000 |
commit | efba054640d3418d7477316ae0c1e992d0aa0f22 (patch) | |
tree | 25d887fe807edc6c1f53b0d74dde92bfc7d4572f /testsuite/tests/polykinds/T14723.hs | |
parent | 0f43d0dba3da7b16f6d3fd2e7cb6e62ac524eb04 (diff) | |
download | haskell-efba054640d3418d7477316ae0c1e992d0aa0f22.tar.gz |
Prioritise equalities when solving, incl deriveds
We already prioritise equalities when solving, but
Trac #14723 showed that we were not doing so consistently
enough, and as a result the type checker could go into a loop.
Yikes.
See Note [Prioritise equalities] in TcSMonad.
Fixng this bug changed the solve order enough to demonstrate
a problem with fundeps: Trac #14745.
Diffstat (limited to 'testsuite/tests/polykinds/T14723.hs')
-rw-r--r-- | testsuite/tests/polykinds/T14723.hs | 70 |
1 files changed, 70 insertions, 0 deletions
diff --git a/testsuite/tests/polykinds/T14723.hs b/testsuite/tests/polykinds/T14723.hs new file mode 100644 index 0000000000..9b2f3bf75e --- /dev/null +++ b/testsuite/tests/polykinds/T14723.hs @@ -0,0 +1,70 @@ +{-# LANGUAGE DataKinds #-} +{-# LANGUAGE FunctionalDependencies #-} +{-# LANGUAGE KindSignatures #-} +{-# LANGUAGE PolyKinds #-} +{-# LANGUAGE RankNTypes #-} +{-# LANGUAGE TypeFamilies #-} +{-# LANGUAGE UndecidableInstances #-} + +module T14723 () where + +import Data.Coerce( coerce ) +import Data.Kind (Type) +import Data.Proxy (Proxy(..)) +import Data.String (fromString) +import Data.Int (Int64) +import GHC.Stack (HasCallStack) +import GHC.TypeLits (Nat, Symbol) + +data JType = Iface Symbol + +data J (a :: JType) + +newIterator + :: IO (J ('Iface "java.util.Iterator")) +newIterator = do + let tblPtr :: Int64 + tblPtr = undefined + iterator <- + (qqMarker (Proxy :: Proxy "wuggle") + (Proxy :: Proxy "waggle") + (Proxy :: Proxy "tblPtr") + (Proxy :: Proxy 106) + (tblPtr, ()) + Proxy + (undefined :: IO Int)) + undefined + +class Coercible (a :: Type) where + type Ty a :: JType + +instance Coercible Int64 where + type Ty Int64 = Iface "Int64" +instance Coercible Int where + type Ty Int = Iface "Int" + +class Coercibles xs (tys :: k) | xs -> tys +instance Coercibles () () +instance (ty ~ Ty x, Coercible x, Coercibles xs tys) => Coercibles (x, xs) '(ty, tys) + +qqMarker + :: forall + -- k -- the kind variable shows up in Core + (args_tys :: k) -- JType's of arguments + tyres -- JType of result + (input :: Symbol) -- input string of the quasiquoter + (mname :: Symbol) -- name of the method to generate + (antiqs :: Symbol) -- antiquoted variables as a comma-separated list + (line :: Nat) -- line number of the quasiquotation + args_tuple -- uncoerced argument types + b. -- uncoerced result type + (tyres ~ Ty b, Coercibles args_tuple args_tys, Coercible b, HasCallStack) + => Proxy input + -> Proxy mname + -> Proxy antiqs + -> Proxy line + -> args_tuple + -> Proxy args_tys + -> IO b + -> IO b +qqMarker = undefined |