Skip to content

Commit

Permalink
Test for Trac #2238
Browse files Browse the repository at this point in the history
  • Loading branch information
simonpj committed Apr 28, 2008
1 parent c179df0 commit fc2ea08
Show file tree
Hide file tree
Showing 2 changed files with 40 additions and 0 deletions.
39 changes: 39 additions & 0 deletions tests/ghc-regress/indexed-types/should_compile/T2238.hs
@@ -0,0 +1,39 @@
{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE UndecidableInstances #-}
{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE FunctionalDependencies #-}
{-# LANGUAGE MultiParamTypeClasses #-}

-- Trac #2238
-- Notice that class CTF has just one value field, but
-- it also has an equality predicate.
-- See Note [Class newtypes and equality predicates] in BuildTyCl

module Foo where

data A
data B

-- via functional dependencies

class HowFD a how | a -> how

class HowFD a how => CFD a how where
cfd :: a -> String
cfd _ = "cfd"
instance HowFD a how => CFD a how

instance HowFD Bool A

-- via type families

type family HowTF a

class how ~ HowTF a => CTF a how where
ctf :: a -> String
ctf _ = "ctf"

instance how ~ HowTF a => CTF a how

type instance HowTF Bool = A
1 change: 1 addition & 0 deletions tests/ghc-regress/indexed-types/should_compile/all.T
Expand Up @@ -106,3 +106,4 @@ test('GivenCheckTop', normal, compile, [''])

test('Gentle', normal, compile, [''])
test('T1981', normal, compile, [''])
test('T2238', normal, compile, [''])

0 comments on commit fc2ea08

Please sign in to comment.