summaryrefslogtreecommitdiff
path: root/testsuite/tests/deriving/should_compile/drv-functor1.hs
blob: 8249858cae49bd16ef261ccacc7f747e97d9a732 (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
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE ExistentialQuantification #-}
{-# LANGUAGE RankNTypes #-}
{-# LANGUAGE FlexibleContexts #-}
{-# LANGUAGE DatatypeContexts #-}

module ShouldCompile where

data Trivial a = Trivial
   deriving (Functor)

data Fun a = Fun (Int -> a)
  deriving (Functor)

-- lots of different things
data Strange a b c
    = T1 a b c
    | T2 [a] [b] [c]         -- lists
    | T3 [[a]] [[b]] [[c]]   -- nested lists
    | T4 (c,(b,b),(c,c))     -- tuples
    | T5 ([c],Strange a b c) -- tycons
    | T6 (Int -> c)          -- function types
    | T7 (a -> (c,a))        -- functions and tuples 
    | T8 ((c -> a) -> a)     -- continuation
  deriving (Functor)

data NotPrimitivelyRecursive a
    = S1 (NotPrimitivelyRecursive (a,a))
    | S2 a
  deriving (Functor,Eq)

data Eq a => StupidConstraint a b = Stupid a b
  deriving (Functor)

-- requires Functor constraint on f and g
data Compose f g a = Compose (f (g a))
  deriving (Functor)

-- We can't derive Functor for the following type.
-- it needs both (Functor (f Int)) and (Functor (f Bool))
-- i.e.:
--  instance (Functor (f Bool), Functor (f Int)) => Functor (ComplexConstraint f)
-- This requires FlexibleContexts and UndecidableInstances
data ComplexConstraint f a = ComplexContraint (f Int (f Bool a,a))
--  deriving (Functor)

data Universal a
    = Universal  (forall b. (b,[a]))
    | Universal2 (forall f. Functor f => (f a))
    | Universal3 (forall a. a -> Int) -- reuse a
    | NotReallyUniversal (forall b. a)
  deriving (Functor)

-- Ghc doesn't allow deriving for non-Haskell98 data constructors
data Existential b
    = forall a. ExistentialList [a]
    | forall f. Functor f => ExistentialFunctor (f b)
    | forall b. SneakyUseSameName (b -> Bool)
  -- deriving (Functor)

-- Don't get confused by synonyms
type IntFun a = Int -> a
data IntFunD a = IntFunD (IntFun a)
  deriving (Functor)