File: GenericsSpec.hs

package info (click to toggle)
haskell-distributive 0.6.2.1-3
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 124 kB
  • sloc: haskell: 301; makefile: 7
file content (91 lines) | stat: -rw-r--r-- 2,622 bytes parent folder | download | duplicates (4)
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
81
82
83
84
85
86
87
88
89
90
91
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveFunctor #-}
{-# LANGUAGE EmptyDataDecls #-}
{-# LANGUAGE StandaloneDeriving #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeFamilies #-}

#if __GLASGOW_HASKELL__ >= 702
{-# LANGUAGE DeriveGeneric #-}
#endif
-----------------------------------------------------------------------------
-- |
-- Module      :  GenericSpec
-- Copyright   :  (C) 2011-2016 Edward Kmett
-- License     :  BSD-style (see the file LICENSE)
--
-- Maintainer  :  Edward Kmett <ekmett@gmail.com>
-- Stability   :  provisional
--
-- Tests for generically derived 'Distributive' instances.
----------------------------------------------------------------------------
module GenericsSpec (main, spec) where

import Test.Hspec

#if __GLASGOW_HASKELL__ >= 702
import           Data.Distributive (Distributive(..))
import           Data.Distributive.Generic (genericCollect, genericDistribute)

# if __GLASGOW_HASKELL__ >= 706
import           Generics.Deriving.Base hiding (Rep)
# else
import qualified Generics.Deriving.TH as Generics (deriveAll1)
# endif
#endif

main :: IO ()
main = hspec spec

spec :: Spec
#if __GLASGOW_HASKELL__ < 702
spec = return ()
#else
spec = do
  describe "Id" $
    it "distribute idExample = idExample" $
      distribute idExample `shouldBe` idExample
  describe "Stream" $
    it "runId (shead (stail (distribute streamExample))) = 1" $
      runId (shead (stail (distribute streamExample))) `shouldBe` 1
  describe "PolyRec" $
    it "runId (plast (runId (pinit (distribute polyRecExample)))) = 1" $
      runId (plast (runId (pinit (distribute polyRecExample)))) `shouldBe` 1

newtype Id a = Id { runId :: a }
  deriving (Eq, Functor, Show)
instance Distributive Id where
  collect    = genericCollect
  distribute = genericDistribute

idExample :: Id (Id Int)
idExample = Id (Id 42)

data Stream a = (:>) { shead :: a, stail :: Stream a }
  deriving Functor
instance Distributive Stream where
  collect    = genericCollect
  distribute = genericDistribute

streamExample :: Id (Stream Int)
streamExample = Id $ let s = 0 :> fmap (+1) s in s

data PolyRec a = PolyRec { pinit :: Id (PolyRec a), plast :: a }
  deriving Functor
instance Distributive PolyRec where
  collect    = genericCollect
  distribute = genericDistribute

polyRecExample :: Id (PolyRec Int)
polyRecExample = Id $ let p = PolyRec (Id $ fmap (+1) p) 0 in p

# if __GLASGOW_HASKELL__ >= 706
deriving instance Generic1 Id
deriving instance Generic1 Stream
deriving instance Generic1 PolyRec
# else
$(Generics.deriveAll1 ''Id)
$(Generics.deriveAll1 ''Stream)
$(Generics.deriveAll1 ''PolyRec)
# endif
#endif