
#12788: While using Data.Aeson.TH, "Irrefutable pattern failed for pattern sel_id : _" -------------------------------------+------------------------------------- Reporter: jchia | Owner: Type: bug | Status: new Priority: normal | Milestone: Component: Compiler | Version: 8.0.1 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): Here's a version which doesn't require installing `aeson`: {{{#!hs -- Bug2.hs module Bug2 where import Language.Haskell.TH data Options = Options { fieldLabelModifier :: String -> String , constructorTagModifier :: String -> String , allNullaryToStringTag :: Bool , omitNothingFields :: Bool , sumEncoding :: SumEncoding , unwrapUnaryRecords :: Bool } data SumEncoding = TaggedObject { tagFieldName :: String , contentsFieldName :: String } | ObjectWithSingleField | TwoElemArray deriveJSON :: Options -> Name -> Q [Dec] deriveJSON _ _ = return [] }}} {{{#!hs -- Bug.hs {-# LANGUAGE TemplateHaskell #-} module Bug where import Bug2 import Language.Haskell.TH data Bad = Bad { _bad :: String } deriving (Eq, Ord, Show) $(deriveJSON defaultOptions{} ''Bad) }}} {{{ $ /opt/ghc/head/bin/ghc Bug.hs [1 of 2] Compiling Bug2 ( Bug2.hs, Bug2.o ) [2 of 2] Compiling Bug ( Bug.hs, Bug.o ) ghc: panic! (the 'impossible' happened) (GHC version 8.1.20161010 for x86_64-unknown-linux): compiler/typecheck/TcExpr.hs:820:15-35: Irrefutable pattern failed for pattern sel_id : _ Please report this as a GHC bug: http://www.haskell.org/ghc/reportabug }}} -- Ticket URL: http://ghc.haskell.org/trac/ghc/ticket/12788#comment:2 GHC http://www.haskell.org/ghc/ The Glasgow Haskell Compiler