[GHC] #15043: Expand type synonym

#15043: Expand type synonym -------------------------------------+------------------------------------- Reporter: domenkozar | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler | Version: 8.2.2 (Type checker) | Keywords: | Operating System: Unknown/Multiple Architecture: | Type of failure: None/Unknown Unknown/Multiple | Test Case: | Blocked By: Blocking: | Related Tickets: Differential Rev(s): | Wiki Page: -------------------------------------+------------------------------------- Using GHC 8.2.2 and `stack build --ghc-options=-fprint-expanded-synonyms` I have the following type synonym for servant: {{{#!hs type Get302 (cts :: [*]) (hs :: [*]) = Verb 'GET 302 cts (Headers (Header "Location" String ': hs) NoContent) }}} and get the following error message when `String` is mismatched for `Text`: {{{ • Couldn't match type ‘Text’ with ‘[Char]’ Expected type: AsServerT App :- ("login" :> ("callback" :> (QueryParam "code" Text :> (QueryParam "state" Text :> MyApp.Types.Servant.Get302 '[PlainText] '[Header "Set-Cookie" SetCookie, Header "Set-Cookie" SetCookie])))) Actual type: Maybe Code -> Maybe Text -> App (Headers '[Header "Location" Text, Header "Set- Cookie" SetCookie, Header "Set-Cookie" SetCookie] NoContent) }}} The error is confusing as type synonym is not expanded and offending `Header` is missing from the output. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15043 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15043: Expand type synonym -------------------------------------+------------------------------------- Reporter: domenkozar | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: Operating System: Unknown/Multiple | Architecture: | Unknown/Multiple Type of failure: None/Unknown | Test Case: Blocked By: | Blocking: Related Tickets: | Differential Rev(s): Wiki Page: | -------------------------------------+------------------------------------- Description changed by domenkozar: Old description:
Using GHC 8.2.2 and `stack build --ghc-options=-fprint-expanded-synonyms` I have the following type synonym for servant:
{{{#!hs type Get302 (cts :: [*]) (hs :: [*]) = Verb 'GET 302 cts (Headers (Header "Location" String ': hs) NoContent) }}}
and get the following error message when `String` is mismatched for `Text`:
{{{ • Couldn't match type ‘Text’ with ‘[Char]’ Expected type: AsServerT App :- ("login" :> ("callback" :> (QueryParam "code" Text :> (QueryParam "state" Text :> MyApp.Types.Servant.Get302 '[PlainText] '[Header "Set-Cookie" SetCookie, Header "Set-Cookie" SetCookie])))) Actual type: Maybe Code -> Maybe Text -> App (Headers '[Header "Location" Text, Header "Set- Cookie" SetCookie, Header "Set-Cookie" SetCookie] NoContent) }}}
The error is confusing as type synonym is not expanded and offending `Header` is missing from the output.
New description: Using GHC 8.2.2 and `stack build --ghc-options=-fprint-expanded-synonyms` I have the following type synonym for servant: {{{#!hs type Get302 (cts :: [*]) (hs :: [*]) = Verb 'GET 302 cts (Headers (Header "Location" String ': hs) NoContent) }}} and get the following error message when `String` is mismatched for `Text`: {{{ • Couldn't match type ‘Text’ with ‘[Char]’ Expected type: AsServerT App :- ("login" :> ("callback" :> (QueryParam "code" Text :> (QueryParam "state" Text :> MyApp.Types.Servant.Get302 '[PlainText] '[Header "Set-Cookie" SetCookie, Header "Set-Cookie" SetCookie])))) Actual type: Maybe Code -> Maybe Text -> App (Headers '[Header "Location" Text, Header "Set- Cookie" SetCookie, Header "Set-Cookie" SetCookie] NoContent) }}} The error is confusing as type synonym is not expanded and offending `Header` is missing from the output in the expected type. -- -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15043#comment:1 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15043: Expand type synonym -------------------------------------+------------------------------------- Reporter: domenkozar | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: 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 RyanGlScott): Is that the entirety of the error message? I ask because if I try using `-fprint-expanded-synonyms` on a smaller program, such as this one: {{{#!hs module Bug where type Foo = Int f :: Maybe Foo f = Just 'a' }}} I get this: {{{ $ ghc Bug.hs -fprint-expanded-synonyms [1 of 1] Compiling Bug ( Bug.hs, Bug.o ) Bug.hs:6:5: error: • Couldn't match type ‘Char’ with ‘Int’ Expected type: Maybe Foo Actual type: Maybe Char Type synonyms expanded: Expected type: Maybe Int Actual type: Maybe Char • In the expression: Just 'a' In an equation for ‘f’: f = Just 'a' | 6 | f = Just 'a' | ^^^^^^^^ }}} Notice that there is a separate `Type synonyms expanded` section which shows `Maybe Int` instead of `Maybe Foo`. Does GHC not show this in your example? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15043#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15043: Expand type synonym -------------------------------------+------------------------------------- Reporter: domenkozar | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: 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 domenkozar): I can reproduce the problem using servant-generic. A minimal example to reproduce: {{{#!hs #!/usr/bin/env nix-shell #!nix-shell -i "runghc --ghc-arg=-fprint-expanded-synonyms" -p "haskellPackages.ghcWithPackages (pkgs: with pkgs; [servant-server servant-auth-server servant-generic])" {-# LANGUAGE DataKinds #-} {-# LANGUAGE TypeOperators #-} {-# LANGUAGE KindSignatures #-} {-# LANGUAGE DeriveGeneric #-} module ApiType where import Data.Text import GHC.Generics import Servant import Servant.Auth.Server import Servant.API import Servant.Generic type Get302 (cts :: [*]) (hs :: [*]) = Verb 'GET 302 cts (Headers (Header "Location" String ': hs) NoContent) type API = ToServant (GenericAPI AsApi) data GenericAPI route = GenericAPI { root :: route :- Get302 '[JSON] '[ Header "Set-Cookie" SetCookie] } deriving Generic server :: Server API server = toServant endpoints endpoints :: GenericAPI AsServer endpoints = GenericAPI { root = handler } handler :: Handler (Headers '[ Header "Location" Text , Header "Set-Cookie" SetCookie] NoContent) handler = undefined main :: IO () main = undefined }}} Yields: {{{ ghc15043.hs:33:12: error: • Couldn't match type ‘Text’ with ‘[Char]’ Expected type: AsServer :- Get302 '[JSON] '[Header "Set-Cookie" SetCookie] Actual type: Handler (Headers '[Header "Location" Text, Header "Set-Cookie" SetCookie] NoContent) • In the ‘root’ field of a record In the expression: GenericAPI {root = handler} In an equation for ‘endpoints’: endpoints = GenericAPI {root = handler} | 33 | { root = handler | ^^^^^^^ }}} Note that without using servant-generic, I do get type synonyms expanded, although it's not particulary helpful in this case: {{{ works-ghc15043.hs:24:10: error: • Couldn't match type ‘Text’ with ‘[Char]’ Expected type: Server API Actual type: Handler (Headers '[Header "Location" Text, Header "Set-Cookie" SetCookie] NoContent) Type synonyms expanded: Expected type: ServerT API Handler Actual type: Handler (Headers '[Header "Location" Text, Header "Set-Cookie" SetCookie] NoContent) • In the expression: handler In an equation for ‘server’: server = handler | 24 | server = handler | ^^^^^^^ }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15043#comment:3 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15043: Expand type synonym -------------------------------------+------------------------------------- Reporter: domenkozar | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: 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 alpmestan): * cc: alpmestan (added) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15043#comment:4 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15043: Expand type synonym -------------------------------------+------------------------------------- Reporter: domenkozar | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: 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): * cc: osa1 (added) Comment: OK, I believe I can reproduce the essence of this with the following, smaller example: {{{#!hs module Bug where type Foo = Int f :: Maybe Foo f = ['a'] }}} {{{ $ ghci Bug.hs -fprint-expanded-synonyms GHCi, version 8.4.1: http://www.haskell.org/ghc/ :? for help Loaded GHCi configuration from /home/rgscott/.ghci [1 of 1] Compiling Bug ( Bug.hs, interpreted ) Bug.hs:6:5: error: • Couldn't match expected type ‘Maybe Foo’ with actual type ‘[Char]’ • In the expression: ['a'] In an equation for ‘f’: f = ['a'] | 6 | f = ['a'] | ^^^^^ }}} Note that this error message does not expand `Foo`. That being said, the GHC commentary would suggest that this is intentional. See [http://git.haskell.org/ghc.git/blob/5d76846405240c051b00cddcda9d8d02c880968e... this Note]: {{{#!hs {- Note [Expanding type synonyms to make types similar] ~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~~ In type error messages, if -fprint-expanded-types is used, we want to expand type synonyms to make expected and found types as similar as possible, but we shouldn't expand types too much to make type messages even more verbose and harder to understand. The whole point here is to make the difference in expected and found types clearer. `expandSynonymsToMatch` does this, it takes two types, and expands type synonyms only as much as necessary. Given two types t1 and t2: * If they're already same, it just returns the types. * If they're in form `C1 t1_1 .. t1_n` and `C2 t2_1 .. t2_m` (C1 and C2 are type constructors), it expands C1 and C2 if they're different type synonyms. Then it recursively does the same thing on expanded types. If C1 and C2 are same, then it applies the same procedure to arguments of C1 and arguments of C2 to make them as similar as possible. Most important thing here is to keep number of synonym expansions at minimum. For example, if t1 is `T (T3, T5, Int)` and t2 is `T (T5, T3, Bool)` where T5 = T4, T4 = T3, ..., T1 = X, it returns `T (T3, T3, Int)` and `T (T3, T3, Bool)`. * Otherwise types don't have same shapes and so the difference is clearly visible. It doesn't do any expansions and show these types. Note that we only expand top-layer type synonyms. Only when top-layer constructors are the same we start expanding inner type synonyms. -} }}} Since the "top-level constructors" in this example, `Maybe` and `[]`, are different, it avoids expanding the type synonyms in their arguments. The same reason applies to your example, since the "top-level constructors" are `(:-)` and `Handler`, which are different. osa1, you implemented `-fprint-expanded-synonyms` in ae96c751c869813ab95e712f8daac8516bb4795f. Do you agree with this analysis? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15043#comment:5 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15043: Expand type synonym -------------------------------------+------------------------------------- Reporter: domenkozar | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: 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 domenkozar): Although I don't know enough to judge the conclusion in the comment, it seems like it's a zero sum game unless there's a way to tweak level/verbosity of expansion or be able to interactively dig in. Thanks for helping me figure this one out. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15043#comment:6 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15043: Expand type synonym -------------------------------------+------------------------------------- Reporter: domenkozar | Owner: (none) Type: bug | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: 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 osa1): RyanGlScott, your analysis is correct, this is by design. It's impossible to provide one flag that'll make everyone happy, because expanding _all_ synonyms (as noted in the note quoted in comment:5) often results in huge types that are impossible to compare -- that's why we choose to expand until the difference becomes apparent. So perhaps we can provide another flag for expanding _all_ synonyms when needed (although I'm not sure if that'd result in reasonably-sized types in this case -- servant's types are quite complex!) -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15043#comment:7 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15043: Expand type synonym -------------------------------------+------------------------------------- Reporter: domenkozar | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: 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 => infoneeded Comment: Domen, would a variant of `-fprint-expanded-synonyms` that expanded all type synonyms work for your use case? -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15043#comment:8 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15043: Expand type synonym -------------------------------------+------------------------------------- Reporter: domenkozar | Owner: (none) Type: bug | Status: infoneeded Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: 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 domenkozar): I'm not entirely sure as I don't have enough experience. I do think having a way to expand all type synonyms means to at least see what's going on, but I don't think it is the best solution (as per osa1 concern that errors will get verbose). Maybe worth a try and see how it behaves in servant - something that many haskell devs will face. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15043#comment:9 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15043: A more aggressive version of -fprint-expanded-synonyms that prints all type synonyms -------------------------------------+------------------------------------- Reporter: domenkozar | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: 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: infoneeded => new * type: bug => feature request -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15043#comment:10 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler

#15043: A more aggressive version of -fprint-expanded-synonyms that prints all type synonyms -------------------------------------+------------------------------------- Reporter: domenkozar | Owner: (none) Type: feature request | Status: new Priority: normal | Milestone: 8.6.1 Component: Compiler (Type | Version: 8.2.2 checker) | Resolution: | Keywords: 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 bgamari): As osa1 mentioned, it seems that the UI design here is quite thorny. Frankly, this is an area where I think more interactive errors (e.g. ticket:8809#comment: will help immensely and may be the only satisfactory solution (#8809). Richard has a student working on laying the groundwork for this over the summer. -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/15043#comment:11 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler
participants (1)
-
GHC