[GHC] #15601: Unexpected compile error on type level lists with a single element

#15601: Unexpected compile error on type level lists with a single element -------------------------------------+------------------------------------- Reporter: erikd | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: Incorrect Unknown/Multiple | error/warning at compile-time Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Tried this with ghc 8.0.2, 8.2.2 and 8.4.3 and all give an almost identical error on the following piece of code: {{{#!hs {-# LANGUAGE FlexibleContexts #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE DataKinds #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE PolyKinds #-} {-# LANGUAGE CPP #-} {-# OPTIONS_GHC -Wall #-} import Data.Singletons.Prelude.List #if MIN_VERSION_singletons(2,4,0) type (a :++ b) = a ++ b #endif data MyType = A | B | C | D | E | F type TypeList1 = ['A, 'B] type TypeList2 = TypeList1 :++ ['C, 'D] -- Everything above is fine, but this line: type TypeList3 = TypeList2 :++ ['F] -- Gives the error: -- -- type-level-list.hs:21:32: error: -- • Expected kind ‘[MyType]’, but ‘[ 'F]’ has kind ‘*’ -- • In the second argument of ‘(:++)’, namely ‘[ 'F]’ -- In the type ‘TypeList2 :++ [ 'F]’ -- In the type declaration for ‘TypeList3’ -- | -- 22 | type TypeList3 = TypeList2 :++ ['F] -- If instead I write it like: type TypeList4 = TypeList2 :++ '[F] -- I get the warning: -- -- type-level-list.hs:33:34: warning: [-Wunticked-promoted- constructors] -- Unticked promoted constructor: ‘F’. -- Use ‘'F’ instead of ‘F’. -- The following actually seems to work, but I don't understand why type level -- lists containing only one element are different. type TypeList5 = TypeList2 :++ '[ 'F] }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15601 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15601: Unexpected compile error on type level lists with a single element -------------------------------------+------------------------------------- Reporter: erikd | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Changes (by monoidal): * status: new => closed * resolution: => invalid Comment: This is unfortunately by design. When type-level lists were added, the syntax `[a]` was already taken. For example `[Integer]` is a list of integers, kind `*`. It's not a type-level list with one entry, which would be kind `[*]`. If we could start Haskell from scratch I would vote for having `['a', 'b'] :: List Char` instead of `['a', 'b'] :: [Char]` but it's too late to change. See https://downloads.haskell.org/~ghc/latest/docs/html/users_guide/glasgow_exts... #promoted-list-and-tuple-types -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15601#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15601: Unexpected compile error on type level lists with a single element -------------------------------------+------------------------------------- Reporter: erikd | Owner: (none) Type: bug | Status: closed Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.4.3 Resolution: invalid | Keywords: Operating System: Unknown/Multiple | Architecture: Type of failure: Incorrect | Unknown/Multiple error/warning at compile-time | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Comment (by erikd): Ok, thanks. The solution for single element lists is to use: {{{ type TypeList5 = TypeList2 :++ '[ 'F] }}} where bot the list and the constructor are ticked *and* there is a space between the open square bracket and the first ticked constructor. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15601#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC