[GHC] #13673: Core lint error with defer-typed-holes
GHC
ghc-devs at haskell.org
Tue May 9 16:33:18 UTC 2017
#13673: Core lint error with defer-typed-holes
-------------------------------------+-------------------------------------
Reporter: Iceland_jack | Owner: (none)
Type: bug | Status: new
Priority: normal | Milestone:
Component: Compiler | Version: 8.0.1
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:
-------------------------------------+-------------------------------------
Another Core Lint error
{{{#!hs
{-# Options_GHC -dcore-lint -fdefer-typed-holes #-}
{-# Language ViewPatterns, PatternSynonyms, GeneralizedNewtypeDeriving,
DeriveTraversable #-}
import Data.Bifunctor.Fix
import Data.Bifunctor.Tannen
import Test.QuickCheck
import Test.QuickCheck.Function
import Control.Applicative
newtype ZL a = ZL { getZL :: Fix (Tannen Maybe (,)) a }
deriving (Eq, Ord, Read, Show, Functor, Applicative, Foldable,
Traversable)
fromList :: [a] -> ZL a
fromList [] = Nil
fromList (x:xs) = x:::fromList xs
pattern Nil :: ZL a
pattern Nil = ZL (In (Tannen Nothing))
foo :: ZL a -> Maybe (a, ZL a)
foo (ZL (In (Tannen (Just (as, a))))) = Just (a, ZL as)
infixr 5 :::
pattern (:::) :: a -> ZL a -> ZL a
pattern a:::as <- ZL (In (Tannen (Just (ZL -> as, a))))
where a:::ZL as = ZL (In (Tannen (Just (as, a))))
u (Fn f) as bs = let
(xs, ys) = (ZipList as, ZipList bs)
in getZipList (liftA2 f xs ys) == toList (liftA2 f (fromList as)
(fromList bs))
}}}
unfortunately I don't have time to reduce it
--
Ticket URL: <http://ghc.haskell.org/trac/ghc/ticket/13673>
GHC <http://www.haskell.org/ghc/>
The Glasgow Haskell Compiler
More information about the ghc-tickets
mailing list