File: GH31Spec.hs

package info (click to toggle)
haskell-deriving-compat 0.6.6-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 492 kB
  • sloc: haskell: 6,121; makefile: 5
file content (59 lines) | stat: -rw-r--r-- 1,235 bytes parent folder | download | duplicates (3)
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
{-# LANGUAGE TemplateHaskell #-}

{-|
Module:      GH31Spec
Copyright:   (C) 2020 Ryan Scott
License:     BSD-style (see the file LICENSE)
Maintainer:  Ryan Scott
Portability: Template Haskell

A regression test for
https://github.com/haskell-compat/deriving-compat/issues/31.
-}
module GH31Spec (main, spec) where

import Data.Deriving (deriveEq1, deriveOrd1)
import Data.Functor.Classes (compare1)
import Data.Proxy (Proxy(..))
import Data.Void (Void)

import OrdSpec (ordSpec)

import Prelude ()
import Prelude.Compat

import Test.Hspec (Spec, describe, hspec, it, parallel, shouldBe)
import Test.QuickCheck (Arbitrary(..), oneof)

data T a
  = A
  | B Int
  | C Int
  | D
  | E Int
  | F
  deriving (Eq, Ord, Show)

deriveEq1 ''T
deriveOrd1 ''T

instance Arbitrary (T a) where
  arbitrary = oneof [ pure A
                    , B <$> arbitrary
                    , C <$> arbitrary
                    , pure D
                    , E <$> arbitrary
                    , pure F
                    ]

main :: IO ()
main = hspec spec

spec :: Spec
spec = parallel $
  describe "GH31" $ do
    ordSpec (Proxy :: Proxy (T Void))
    it "obeys reflexivity" $
      let x :: T Void
          x = E 0
      in compare1 x x `shouldBe` EQ