
#13950: IncoherentInstances -------------------------------------+------------------------------------- Reporter: zaoqi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Keywords: | Operating System: Unknown/Multiple IncoherentInstances | Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- {{{#!hs --Copyright (C) 2017 Zaoqi --This program is free software: you can redistribute it and/or modify --it under the terms of the GNU Affero General Public License as published --by the Free Software Foundation, either version 3 of the License, or --(at your option) any later version. --This program is distributed in the hope that it will be useful, --but WITHOUT ANY WARRANTY; without even the implied warranty of --MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the --GNU Affero General Public License for more details. --You should have received a copy of the GNU Affero General Public License --along with this program. If not, see http://www.gnu.org/licenses/. {-# LANGUAGE DataKinds, TypeOperators, KindSignatures, GADTs, MultiParamTypeClasses, FlexibleInstances, FlexibleContexts, AllowAmbiguousTypes, UndecidableInstances, NoMonomorphismRestriction #-} module Data.U where data U :: [*] -> * where UOne :: x -> U (x : xs) USucc :: U xs -> U (x : xs) class Usuccs a b where usuccs :: U a -> U b instance Usuccs a a where usuccs = id instance Usuccs xs ys => Usuccs xs (y : ys) where usuccs xs = USucc (usuccs xs) u x = usuccs (UOne x) }}} {{{ GHCi, version 8.0.2: http://www.haskell.org/ghc/ :? for help Prelude> :load U.hs [1 of 1] Compiling Data.U ( U.hs, interpreted ) Ok, modules loaded: Data.U. *Data.U> :set -XDataKinds *Data.U> (u 'c')::U [String, Char, Int] <interactive>:3:2: error: • Overlapping instances for Usuccs (Char : xs0) '[Char, Int] arising from a use of ‘u’ Matching instances: instance [safe] Usuccs a a -- Defined at U.hs:25:10 ...plus one instance involving out-of-scope types (use -fprint-potential-instances to see them all) (The choice depends on the instantiation of ‘xs0’ To pick the first instance above, use IncoherentInstances when compiling the other instance declarations) • In the expression: (u 'c') :: U '[String, Char, Int] In an equation for ‘it’: it = (u 'c') :: U '[String, Char, Int] }}} {{{#!hs --Copyright (C) 2017 Zaoqi --This program is free software: you can redistribute it and/or modify --it under the terms of the GNU Affero General Public License as published --by the Free Software Foundation, either version 3 of the License, or --(at your option) any later version. --This program is distributed in the hope that it will be useful, --but WITHOUT ANY WARRANTY; without even the implied warranty of --MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the --GNU Affero General Public License for more details. --You should have received a copy of the GNU Affero General Public License --along with this program. If not, see http://www.gnu.org/licenses/. {-# LANGUAGE DataKinds, TypeOperators, KindSignatures, GADTs, MultiParamTypeClasses, FlexibleInstances, FlexibleContexts, AllowAmbiguousTypes, UndecidableInstances, IncoherentInstances, NoMonomorphismRestriction #-} module Data.U where data U :: [*] -> * where UOne :: x -> U (x : xs) USucc :: U xs -> U (x : xs) class Usuccs a b where usuccs :: U a -> U b instance Usuccs a a where usuccs = id instance Usuccs xs ys => Usuccs xs (y : ys) where usuccs xs = USucc (usuccs xs) u x = usuccs (UOne x) }}} {{{ GHCi, version 8.0.2: http://www.haskell.org/ghc/ :? for help Prelude> :load U.hs [1 of 1] Compiling Data.U ( U.hs, interpreted ) Ok, modules loaded: Data.U. *Data.U> :set -XDataKinds *Data.U> (u 'c')::U [String, Char, Int] <interactive>:3:2: error: • No instance for (Usuccs (Char : xs0) '[]) arising from a use of ‘u’ • In the expression: (u 'c') :: U '[String, Char, Int] In an equation for ‘it’: it = (u 'c') :: U '[String, Char, Int] }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13950 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13950: IncoherentInstances -------------------------------------+------------------------------------- Reporter: zaoqi | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: | Keywords: | IncoherentInstances Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by hsyl20): {{{#!hs {-# LANGUAGE DataKinds, TypeOperators, KindSignatures, GADTs, MultiParamTypeClasses, FlexibleInstances, FlexibleContexts, AllowAmbiguousTypes, UndecidableInstances, IncoherentInstances, NoMonomorphismRestriction #-} {-# LANGUAGE ScopedTypeVariables #-} module Data.U where data U :: [*] -> * where UOne :: x -> U (x : xs) USucc :: U xs -> U (x : xs) class Usuccs a b where usuccs :: U a -> U b instance Usuccs a a where usuccs = id instance Usuccs xs ys => Usuccs (x : xs) (x : ys) where usuccs (UOne x) = UOne x usuccs (USucc xs) = USucc (usuccs xs) instance Usuccs xs (x : xs) where usuccs = USucc instance Usuccs xs ys => Usuccs xs (y : ys) where usuccs x = USucc (usuccs x) instance Show x => Show (U '[x]) where show (UOne x) = "(u " ++ showsPrec 11 x ")" instance (Show x, Show (U xs)) => Show (U (x : xs)) where show (UOne x) = "(u " ++ showsPrec 11 x ")" show (USucc xs) = show xs u :: forall t x. Usuccs '[x] t => x -> U t u x = usuccs (UOne x :: U '[x]) }}} {{{#!bash
:set -XDataKinds (u 'c')::U [String, Char, Int] (u 'c') }}}
? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13950#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#13950: IncoherentInstances -------------------------------------+------------------------------------- Reporter: zaoqi | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: Component: Compiler | Version: 8.0.2 Resolution: invalid | Keywords: | IncoherentInstances Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by RyanGlScott): * status: new => closed * resolution: => invalid Comment: I think hsyl20 nailed it. I believe this is nothing more than an issue of type variable scoping with `forall` (which I clarified further in #13953). Please reopen if you disagree. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/13950#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC