File: Typeable.hs

package info (click to toggle)
haskell-text-show 3.10.5-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 1,148 kB
  • sloc: haskell: 8,817; ansic: 23; makefile: 6
file content (142 lines) | stat: -rw-r--r-- 4,147 bytes parent folder | download | duplicates (2)
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
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
{-# LANGUAGE CPP                 #-}
{-# LANGUAGE MagicHash           #-}
{-# LANGUAGE PolyKinds           #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE StandaloneDeriving  #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}

{-|
Module:      Instances.Data.Typeable
Copyright:   (C) 2014-2017 Ryan Scott
License:     BSD-style (see the file LICENSE)
Maintainer:  Ryan Scott
Stability:   Provisional
Portability: GHC

'Arbitrary' instances for data types in the "Data.Typeable" module.
-}
module Instances.Data.Typeable () where

#include "MachDeps.h"

#if MIN_VERSION_base(4,9,0)
import GHC.Types (TyCon(..), TrName(..), Module(..))
# if MIN_VERSION_base(4,17,0) || WORD_SIZE_IN_BITS < 64
import GHC.Word (Word64(..))
# else
import GHC.Word (Word(..))
# endif
#else
import Data.Typeable.Internal (TyCon(..))
#endif

#if MIN_VERSION_base(4,10,0)
import GHC.Exts (Int(..), Ptr(..))
import GHC.Types ( KindRep(..), RuntimeRep(..), TypeLitSort(..)
                 , VecCount(..), VecElem(..)
# if MIN_VERSION_base(4,16,0)
                 , Levity(..)
# endif
                 )
import Type.Reflection (SomeTypeRep(..), Typeable, TypeRep, typeRep)
#else
import Data.Typeable.Internal (TypeRep(..))
#endif

import Instances.Foreign.Ptr ()
import Instances.GHC.Fingerprint ()
import Instances.Utils ((<@>))

import Prelude ()
import Prelude.Compat

import Test.QuickCheck

#if MIN_VERSION_base(4,10,0)
instance Typeable a => Arbitrary (TypeRep (a :: k)) where
    arbitrary = pure (typeRep :: TypeRep (a :: k))

instance Arbitrary SomeTypeRep where
    arbitrary = SomeTypeRep <$> (arbitrary :: Gen (TypeRep Int))

deriving instance Bounded TypeLitSort
deriving instance Enum TypeLitSort
instance Arbitrary TypeLitSort where
    arbitrary = arbitraryBoundedEnum

instance Arbitrary KindRep where
    arbitrary = oneof [ KindRepTyConApp <$> arbitrary <@> []
                      , KindRepVar <$> arbitrary
                      , KindRepApp <$> krt <*> krt
                      , krt
                      , do Ptr a# <- arbitrary
                           (\a -> KindRepTypeLitS a a#) <$> arbitrary
                      , KindRepTypeLitD <$> arbitrary <*> arbitrary
                      ]
      where
        krt = KindRepTYPE <$> arbitrary

instance Arbitrary RuntimeRep where
    arbitrary = oneof [ VecRep <$> arbitrary <*> arbitrary
                      , pure $ TupleRep []
                      , pure $ SumRep []
# if MIN_VERSION_base(4,16,0)
                      , pure $ BoxedRep Lifted
                      , pure $ BoxedRep Unlifted
# else
                      , pure LiftedRep
                      , pure UnliftedRep
# endif
                      , pure IntRep
                      , pure WordRep
                      , pure Int64Rep
                      , pure Word64Rep
                      , pure AddrRep
                      , pure FloatRep
                      , pure DoubleRep
                      ]

instance Arbitrary VecCount where
    arbitrary = arbitraryBoundedEnum

instance Arbitrary VecElem where
    arbitrary = arbitraryBoundedEnum
#else /* !(MIN_VERSION_base(4,10,0) */
instance Arbitrary TypeRep where
    arbitrary = TypeRep <$> arbitrary
                        <*> arbitrary
# if MIN_VERSION_base(4,8,0)
                        <@> [] <@> []
# else
                        <@> []
# endif
#endif

instance Arbitrary TyCon where
#if MIN_VERSION_base(4,9,0)
    arbitrary = do
# if MIN_VERSION_base(4,17,0) || WORD_SIZE_IN_BITS < 64
        W64# w1# <- arbitrary
        W64# w2# <- arbitrary
# else
        W#   w1# <- arbitrary
        W#   w2# <- arbitrary
# endif
# if MIN_VERSION_base(4,10,0)
        I# i# <- arbitrary
        (\a1 a2 a3 -> TyCon w1# w2# a1 a2 i# a3)
            <$> arbitrary <*> arbitrary <*> arbitrary
# else
        TyCon w1# w2# <$> arbitrary <*> arbitrary
# endif
#else
    arbitrary = TyCon <$> arbitrary <*> arbitrary <*> arbitrary <*> arbitrary
#endif

#if MIN_VERSION_base(4,9,0)
instance Arbitrary TrName where
    arbitrary = oneof [pure (TrNameS "wat"#), TrNameD <$> arbitrary]

instance Arbitrary Module where
    arbitrary = Module <$> arbitrary <*> arbitrary
#endif