summaryrefslogtreecommitdiff
path: root/testsuite/tests/indexed-types/should_fail/T13784.hs
blob: 48982769a21423b34e6e531a32c83b5a91a0e063 (plain)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
{-# LANGUAGE DataKinds, FlexibleContexts, FlexibleInstances, GADTs #-}
{-# LANGUAGE KindSignatures, MultiParamTypeClasses, TypeFamilies,
             TypeOperators #-}

module T13784 where

import Data.Kind (Type)
import Data.Monoid ((<>))

data Product :: [Type] -> Type where
    (:*) :: a -> Product as -> Product (a : as)
    Unit :: Product '[]
infixr 5 :*

instance Show (Product '[]) where
    show Unit = "Unit"

instance (Show a, Show (Product as)) => Show (Product (a : as)) where
    show (a :* as) = show a <> " :* " <> show as

class Divideable a as where
    type Divide a as :: [Type]
    divide :: Product as -> (a, Product (Divide a as))

instance Divideable a (a : as) where
    -- type Divide a (a : as) = as
    -- Conflicting type family instances, seems like OVERLAPS isn't a thing for
    -- type families.
    divide (a :* as) = (a, as)

instance Divideable b as => Divideable b (a : as) where
    type Divide b (a : as) = a : Divide b as
    divide (a :* as) = a :* divide as