File: Main.hs

package info (click to toggle)
haskell-isomorphism-class 0.1.1-1
  • links: PTS
  • area: main
  • in suites: forky, sid, trixie
  • size: 88 kB
  • sloc: haskell: 529; makefile: 5
file content (127 lines) | stat: -rw-r--r-- 6,724 bytes parent folder | download
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
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
module Main where

import qualified Data.ByteString.Builder as ByteStringBuilder
import qualified Data.ByteString.Lazy as ByteStringLazy
import qualified Data.ByteString.Short as ByteStringShort
import qualified Data.Primitive.ByteArray as PrimitiveByteArray
import qualified Data.Text.Lazy as TextLazy
import qualified Data.Text.Lazy.Builder as TextLazyBuilder
import IsomorphismClass
import Rebase.Prelude
import Test.ExtraInstances ()
import Test.Tasty
import Test.Tasty.QuickCheck hiding ((.&.))

main :: IO ()
main = defaultMain allTests

allTests :: TestTree
allTests =
  testGroup "All" $
    [ testPair @String @Text Proxy Proxy,
      testPair @String @TextLazy.Text Proxy Proxy,
      testPair @String @TextLazyBuilder.Builder Proxy Proxy,
      testPair @[Word8] @ByteString Proxy Proxy,
      testPair @[Word8] @ByteStringLazy.ByteString Proxy Proxy,
      testPair @[Word8] @ByteStringShort.ShortByteString Proxy Proxy,
      testPair @[Word8] @ByteStringBuilder.Builder Proxy Proxy,
      testPair @[Word8] @PrimitiveByteArray.ByteArray Proxy Proxy,
      testPair @[Word8] @[Word8] Proxy Proxy,
      testPair @[Word8] @(Vector Word8) Proxy Proxy,
      testPair @[Word8] @(Seq Word8) Proxy Proxy,
      testPair @Text @Text Proxy Proxy,
      testPair @Text @String Proxy Proxy,
      testPair @Text @TextLazy.Text Proxy Proxy,
      testPair @Text @TextLazyBuilder.Builder Proxy Proxy,
      testPair @TextLazy.Text @TextLazy.Text Proxy Proxy,
      testPair @TextLazy.Text @String Proxy Proxy,
      testPair @TextLazy.Text @Text Proxy Proxy,
      testPair @TextLazy.Text @TextLazyBuilder.Builder Proxy Proxy,
      testPair @TextLazyBuilder.Builder @TextLazyBuilder.Builder Proxy Proxy,
      testPair @TextLazyBuilder.Builder @String Proxy Proxy,
      testPair @TextLazyBuilder.Builder @Text Proxy Proxy,
      testPair @TextLazyBuilder.Builder @TextLazy.Text Proxy Proxy,
      testPair @ByteString @ByteString Proxy Proxy,
      testPair @ByteString @[Word8] Proxy Proxy,
      testPair @ByteString @ByteStringLazy.ByteString Proxy Proxy,
      testPair @ByteString @ByteStringShort.ShortByteString Proxy Proxy,
      testPair @ByteString @ByteStringBuilder.Builder Proxy Proxy,
      testPair @ByteString @PrimitiveByteArray.ByteArray Proxy Proxy,
      testPair @ByteStringLazy.ByteString @ByteStringLazy.ByteString Proxy Proxy,
      testPair @ByteStringLazy.ByteString @[Word8] Proxy Proxy,
      testPair @ByteStringLazy.ByteString @ByteString Proxy Proxy,
      testPair @ByteStringLazy.ByteString @ByteStringShort.ShortByteString Proxy Proxy,
      testPair @ByteStringLazy.ByteString @ByteStringBuilder.Builder Proxy Proxy,
      testPair @ByteStringLazy.ByteString @PrimitiveByteArray.ByteArray Proxy Proxy,
      testPair @ByteStringShort.ShortByteString @ByteStringShort.ShortByteString Proxy Proxy,
      testPair @ByteStringShort.ShortByteString @[Word8] Proxy Proxy,
      testPair @ByteStringShort.ShortByteString @ByteString Proxy Proxy,
      testPair @ByteStringShort.ShortByteString @ByteStringLazy.ByteString Proxy Proxy,
      testPair @ByteStringShort.ShortByteString @ByteStringBuilder.Builder Proxy Proxy,
      testPair @ByteStringShort.ShortByteString @PrimitiveByteArray.ByteArray Proxy Proxy,
      testPair @ByteStringBuilder.Builder @ByteStringBuilder.Builder Proxy Proxy,
      testPair @ByteStringBuilder.Builder @[Word8] Proxy Proxy,
      testPair @ByteStringBuilder.Builder @ByteString Proxy Proxy,
      testPair @ByteStringBuilder.Builder @ByteStringLazy.ByteString Proxy Proxy,
      testPair @ByteStringBuilder.Builder @ByteStringShort.ShortByteString Proxy Proxy,
      testPair @ByteStringBuilder.Builder @PrimitiveByteArray.ByteArray Proxy Proxy,
      testPair @PrimitiveByteArray.ByteArray @PrimitiveByteArray.ByteArray Proxy Proxy,
      testPair @PrimitiveByteArray.ByteArray @[Word8] Proxy Proxy,
      testPair @PrimitiveByteArray.ByteArray @ByteStringShort.ShortByteString Proxy Proxy,
      testPair @PrimitiveByteArray.ByteArray @ByteString Proxy Proxy,
      testPair @PrimitiveByteArray.ByteArray @ByteStringLazy.ByteString Proxy Proxy,
      testPair @PrimitiveByteArray.ByteArray @ByteStringBuilder.Builder Proxy Proxy,
      testPair @(Vector Word8) @(Vector Word8) Proxy Proxy,
      testPair @(Vector Word8) @[Word8] Proxy Proxy,
      testPair @(Vector Word8) @(Seq Word8) Proxy Proxy,
      testPair @(Seq Word8) @(Seq Word8) Proxy Proxy,
      testPair @(Seq Word8) @[Word8] Proxy Proxy,
      testPair @(Seq Word8) @(Vector Word8) Proxy Proxy,
      testPair @(Set Word8) @(Set Word8) Proxy Proxy,
      testPair @(Set Int) @IntSet Proxy Proxy,
      testPair @IntSet @IntSet Proxy Proxy,
      testPair @IntSet @(Set Int) Proxy Proxy,
      testPair @(Map Word8 Word8) @(Map Word8 Word8) Proxy Proxy,
      testPair @(Map Int Word8) @(IntMap Word8) Proxy Proxy,
      testPair @(IntMap Word8) @(IntMap Word8) Proxy Proxy,
      testPair @(IntMap Word8) @(Map Int Word8) Proxy Proxy,
      testPair @(Maybe Word8) @(Maybe Word8) Proxy Proxy,
      testPair @(Either Word8 Word8) @(Either Word8 Word8) Proxy Proxy,
      testPair @(First Word8) @(First Word8) Proxy Proxy,
      testPair @(Last Word8) @(Last Word8) Proxy Proxy,
      testPair @(Product Word8) @(Product Word8) Proxy Proxy,
      testPair @(Sum Word8) @(Sum Word8) Proxy Proxy,
      testPair @Bool @Bool Proxy Proxy,
      testPair @Char @Char Proxy Proxy,
      testPair @Double @Double Proxy Proxy,
      testPair @Float @Float Proxy Proxy,
      testPair @Int @Int Proxy Proxy,
      testPair @Int @Word Proxy Proxy,
      testPair @Int16 @Int16 Proxy Proxy,
      testPair @Int16 @Word16 Proxy Proxy,
      testPair @Int32 @Int32 Proxy Proxy,
      testPair @Int32 @Word32 Proxy Proxy,
      testPair @Int64 @Int64 Proxy Proxy,
      testPair @Int64 @Word64 Proxy Proxy,
      testPair @Int8 @Int8 Proxy Proxy,
      testPair @Int8 @Word8 Proxy Proxy,
      testPair @Integer @Integer Proxy Proxy,
      testPair @Rational @Rational Proxy Proxy,
      testPair @Word @Int Proxy Proxy,
      testPair @Word @Word Proxy Proxy,
      testPair @Word16 @Int16 Proxy Proxy,
      testPair @Word16 @Word16 Proxy Proxy,
      testPair @Word32 @Int32 Proxy Proxy,
      testPair @Word32 @Word32 Proxy Proxy,
      testPair @Word64 @Int64 Proxy Proxy,
      testPair @Word64 @Word64 Proxy Proxy,
      testPair @Word8 @Int8 Proxy Proxy,
      testPair @Word8 @Word8 Proxy Proxy
    ]

testPair :: forall a b. (IsomorphicTo a b, Eq a, Arbitrary a, Show a, Typeable a, Typeable b) => Proxy a -> Proxy b -> TestTree
testPair _ _ =
  testProperty name $ \a ->
    a === from @b (from @a a)
  where
    name = show (typeOf (undefined :: a)) <> "/" <> show (typeOf (undefined :: b))