File: Instances.hs

package info (click to toggle)
haskell-twitter-types 0.11.0-3
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 340 kB
  • sloc: haskell: 1,784; makefile: 5
file content (180 lines) | stat: -rw-r--r-- 5,271 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
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
{-# LANGUAGE CPP #-}
{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE TemplateHaskell #-}
{-# LANGUAGE TypeOperators #-}
{-# OPTIONS_GHC -fno-warn-orphans #-}

module Instances where

import Control.Applicative
import Data.Aeson

#if MIN_VERSION_aeson(2, 0, 0)
import Data.Aeson.KeyMap as KeyMap
#else
import Data.HashMap.Strict as KeyMap
#endif
import Data.HashMap.Strict as HashMap
import Data.String
import qualified Data.Text as T
import Data.Time (UTCTime (..), defaultTimeLocale, fromGregorian, readTime)
import Generic.Random
import Test.Tasty.QuickCheck
import Web.Twitter.Types

instance IsString UTCTime where
    fromString = readTime defaultTimeLocale twitterTimeFormat

instance Arbitrary UTCTime where
    arbitrary =
        do
            randomDay <- choose (1, 29) :: Gen Int
            randomMonth <- choose (1, 12) :: Gen Int
            randomYear <- choose (2001, 2002) :: Gen Integer
            randomTime <- choose (0, 86401) :: Gen Int
            return $ UTCTime (fromGregorian randomYear randomMonth randomDay) (fromIntegral randomTime)

instance Arbitrary T.Text where
    arbitrary = T.pack <$> arbitrary

instance Arbitrary Value where
    arbitrary =
        elements
            [ Object KeyMap.empty
            , Object (KeyMap.fromList [("test", Number 2), ("value", String "non empty")])
            ]

-- derive makeArbitrary ''StreamingAPI

instance Arbitrary Status where
    arbitrary = do
        qt <- frequency [(5, Just <$> arbitrary), (95, pure Nothing)] :: Gen (Maybe Status)
        rt <- frequency [(5, Just <$> arbitrary), (95, pure Nothing)] :: Gen (Maybe Status)
        Status <$> arbitrary
            <*> arbitrary
            <*> arbitrary
            <*> arbitrary
            <*> arbitrary
            <*> arbitrary
            <*> arbitrary
            <*> arbitrary
            <*> arbitrary
            <*> arbitrary
            <*> arbitrary
            <*> arbitrary
            <*> arbitrary
            <*> arbitrary
            <*> arbitrary
            <*> arbitrary
            <*> pure Nothing
            <*> pure (statusId <$> qt)
            <*> pure qt
            <*> arbitrary
            <*> arbitrary
            <*> pure rt
            <*> arbitrary
            <*> arbitrary
            <*> arbitrary
            <*> arbitrary
            <*> arbitrary
            <*> arbitrary
            <*> arbitrary
            <*> arbitrary

instance Arbitrary SearchStatus where
    arbitrary = genericArbitraryU
instance Arbitrary SearchMetadata where
    arbitrary = genericArbitraryU
instance Arbitrary RetweetedStatus where
    arbitrary = genericArbitraryU

instance Arbitrary DirectMessage where
    arbitrary = genericArbitrarySingleG customGens
      where
        customGens :: Gen Integer :+ ()
        customGens =
            (getNonNegative <$> arbitrary) :+ ()

instance Arbitrary EventTarget where
    arbitrary = genericArbitraryU
instance Arbitrary Event where
    arbitrary = genericArbitraryU
instance Arbitrary Delete where
    arbitrary = genericArbitraryU
instance Arbitrary User where
    arbitrary = genericArbitraryU
instance Arbitrary List where
    arbitrary = genericArbitraryU
instance Arbitrary HashTagEntity where
    arbitrary = genericArbitraryU
instance Arbitrary UserEntity where
    arbitrary = genericArbitraryU
instance Arbitrary URLEntity where
    arbitrary = genericArbitraryU

instance Arbitrary MediaEntity where
    arbitrary = do
        ms <- arbitrary
        MediaEntity
            <$> arbitrary
            <*> arbitrary
            <*> pure (HashMap.fromList [("medium", ms)])
            <*> arbitrary
            <*> arbitrary
            <*> arbitrary

instance Arbitrary MediaSize where
    arbitrary = genericArbitraryU
instance Arbitrary Coordinates where
    arbitrary = genericArbitraryU

instance Arbitrary Place where
    arbitrary = do
        Place HashMap.empty
            <$> arbitrary
            <*> arbitrary
            <*> arbitrary
            <*> arbitrary
            <*> arbitrary
            <*> arbitrary
            <*> arbitrary
            <*> arbitrary

instance Arbitrary BoundingBox where
    arbitrary = genericArbitraryU
instance Arbitrary Entities where
    arbitrary = genericArbitraryU
instance Arbitrary ExtendedEntities where
    arbitrary = genericArbitraryU
instance Arbitrary Variant where
    arbitrary = genericArbitraryU
instance Arbitrary VideoInfo where
    arbitrary = genericArbitraryU
instance Arbitrary ExtendedEntity where
    arbitrary = do
        ms <- arbitrary
        ExtendedEntity
            <$> arbitrary
            <*> arbitrary
            <*> arbitrary
            <*> pure (HashMap.fromList [("medium", ms)])
            <*> arbitrary
            <*> arbitrary
            <*> arbitrary
            <*> arbitrary
            <*> arbitrary

instance Arbitrary a => Arbitrary (Entity a) where
    arbitrary = do
        a <- arbitrary
        ind <- arbitrary
        return $ Entity a ind

instance Arbitrary Contributor where
    arbitrary = genericArbitraryU
instance Arbitrary ImageSizeType where
    arbitrary = genericArbitraryU
instance Arbitrary UploadedMedia where
    arbitrary = genericArbitraryU
instance Arbitrary DisplayTextRange where
    arbitrary = genericArbitraryU