summaryrefslogtreecommitdiff
path: root/testsuite/tests/backpack/should_compile/bkp15.bkp
blob: c661eafe6f5fa7f74d85a74e2f37caa26335aaea (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
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
{-# LANGUAGE RankNTypes, DatatypeContexts, CApiFFI, GADTs, TypeFamilies, DefaultSignatures, MultiParamTypeClasses, FunctionalDependencies, PatternSynonyms #-}

-- Reflexivity test, bang on the units with as much
-- stuff as we can.
unit p where
    signature H where
        x :: (forall a. a -> a) -> (Int, Bool)
        data Eq a => T a = T (a -> a) | S (S a)
        data S a = R (T a)
        data {-# CTYPE "Foo" #-} Foo where
            Foo :: Foo
        newtype F a = F a
        type X m a = m a
        type family Elem c
        class Eq a => Bloop a b | a -> b where
            data GMap a (v :: * -> *) :: *
            xa :: a -> a -> Bool
            default xa :: a -> a -> Bool
            y :: a -> a -> Ordering
            default y :: Ord a => a -> a -> Ordering
            {-# MINIMAL xa | y #-}
        -- type instance Elem Int = Bool
        -- pattern Blub n = ("foo", n)

-- keept his synced up!
unit q where
    signature H where
        x :: (forall a. a -> a) -> (Int, Bool)
        data Eq a => T a = T (a -> a) | S (S a)
        data S a = R (T a)
        data {-# CTYPE "Foo" #-} Foo where
            Foo :: Foo
        newtype F a = F a
        type X m a = m a
        type family Elem c
        class Eq a => Bloop a b | a -> b where
            data GMap a (v :: * -> *) :: *
            xa :: a -> a -> Bool
            default xa :: a -> a -> Bool
            y :: a -> a -> Ordering
            default y :: Ord a => a -> a -> Ordering
            {-# MINIMAL xa | y #-}
        -- type instance Elem Int = Bool
        -- pattern Blub n = ("foo", n)

unit r where
    dependency p[H=<H>]
    dependency q[H=<H>]
    module M where
        import H
        a = x id
        b = T (id :: String -> String)
        c = S (R b)
        d = F Foo :: X F Foo
        type instance Elem Bool = Int
        instance Bloop Bool Bool where
            data GMap Bool v = GMapBool (v Bool)
            xa a b = a == not b

unit h-impl where
    module H where
        x :: (forall a. a -> a) -> (Int, Bool)
        x f = (f 2, f True)
        data Eq a => T a = T (a -> a) | S (S a)
        data S a = R (T a)
        data {-# CTYPE "Foo" #-} Foo where
            Foo :: Foo
        newtype F a = F a
        type X m a = m a
        type family Elem c
        class Eq a => Bloop a b | a -> b where
            data GMap a (v :: * -> *) :: *
            xa :: a -> a -> Bool
            xa = (==)
            y :: a -> a -> Ordering
            default y :: Ord a => a -> a -> Ordering
            y = compare
            {-# MINIMAL xa | y #-}
unit s where
    dependency r[H=h-impl:H]