
#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