Skip to content

Commit f9535d7

Browse files
Put Arbitrary instances for Cabal types in their own package.
This is with the intention of the new package, cabal-quickcheck-instances, being the blessed location for these orphans, as QuickCheck acquiring a Cabal dependency or vice-versa would be unsuitable. This reduces some duplication (some presumably deliberate, and some apparently accidental) and then some drift between the versions of these instances. Due to #1575, the modules for the new package are shared with Cabal's test-suite. This is less than ideal, but it's a workable hack.
1 parent b57fa37 commit f9535d7

File tree

14 files changed

+455
-332
lines changed

14 files changed

+455
-332
lines changed

Cabal/Cabal.cabal

Lines changed: 12 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -487,10 +487,20 @@ library
487487
-- Small, fast running tests.
488488
test-suite unit-tests
489489
type: exitcode-stdio-1.0
490-
hs-source-dirs: tests
490+
491+
-- Some of the tests need Arbitrary instances. Ideally, we would
492+
-- depend on the cabal-quickcheck-instances library and avoid
493+
-- sharing source, but #1575 makes that impossible (as we'd have a
494+
-- cycle between packages). If/when that's fixed and we arrive in
495+
-- the glorious component-based future, this ugly hack can be
496+
-- removed. In the meantime, as a workaround, we share the source
497+
-- between this component and the c-q-i package.
498+
499+
hs-source-dirs: tests, cabal-quickcheck-instances
491500
other-modules:
501+
Distribution.Arbitrary.Instances
502+
Distribution.Arbitrary.Util
492503
Test.Laws
493-
Test.QuickCheck.Utils
494504
UnitTests.Distribution.Compat.CreatePipe
495505
UnitTests.Distribution.Compat.ReadP
496506
UnitTests.Distribution.Compat.Time
Lines changed: 301 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,301 @@
1+
{-# OPTIONS_GHC -fno-warn-orphans -fno-warn-deprecations #-}
2+
module Distribution.Arbitrary.Instances () where
3+
4+
import Control.Monad
5+
( liftM
6+
, liftM2
7+
)
8+
import Data.Char
9+
( isAlphaNum
10+
, isDigit
11+
)
12+
import Data.List
13+
( intercalate
14+
)
15+
import Distribution.Simple.Flag
16+
( Flag (..)
17+
)
18+
import Distribution.Simple.InstallDirs
19+
( PathTemplate
20+
, toPathTemplate
21+
)
22+
import Distribution.Simple.Utils
23+
( lowercase
24+
)
25+
import Distribution.SPDX
26+
( LicenseId
27+
, LicenseExceptionId
28+
, LicenseExpression (..)
29+
, LicenseListVersion (..)
30+
, LicenseRef
31+
, SimpleLicenseExpression (..)
32+
, licenseExceptionIdList
33+
, licenseIdList
34+
, mkLicenseRef'
35+
)
36+
import Distribution.System
37+
( Arch
38+
, OS
39+
, Platform (..)
40+
, knownArches
41+
, knownOSs
42+
)
43+
import Distribution.Types.Dependency
44+
( Dependency (..)
45+
)
46+
import Distribution.Types.GenericPackageDescription
47+
( FlagName
48+
, mkFlagName
49+
)
50+
import Distribution.Types.LibraryName
51+
( LibraryName (..)
52+
)
53+
import Distribution.Types.PackageName
54+
( PackageName
55+
, mkPackageName
56+
)
57+
import Distribution.Types.UnqualComponentName
58+
( UnqualComponentName
59+
, packageNameToUnqualComponentName
60+
)
61+
import Distribution.Verbosity
62+
( Verbosity
63+
)
64+
import Distribution.Version
65+
( Bound (..)
66+
, LowerBound (..)
67+
, UpperBound (..)
68+
, Version
69+
, VersionInterval
70+
, VersionIntervals
71+
, VersionRange (..)
72+
, anyVersion
73+
, earlierVersion
74+
, intersectVersionRanges
75+
, laterVersion
76+
, majorBoundVersion
77+
, mkVersion
78+
, mkVersionIntervals
79+
, orEarlierVersion
80+
, orLaterVersion
81+
, thisVersion
82+
, unionVersionRanges
83+
, version0
84+
, versionNumbers
85+
, withinVersion
86+
)
87+
import Test.QuickCheck
88+
( Arbitrary ( arbitrary, shrink )
89+
, Gen
90+
, elements
91+
, frequency
92+
, listOf1
93+
, oneof
94+
, sized
95+
, suchThat
96+
)
97+
98+
import Distribution.Arbitrary.Util
99+
100+
-- Instances from Distribution.Simple.Flag
101+
102+
instance Arbitrary a => Arbitrary (Flag a) where
103+
arbitrary = arbitraryFlag arbitrary
104+
shrink NoFlag = []
105+
shrink (Flag x) = NoFlag : [ Flag x' | x' <- shrink x ]
106+
107+
arbitraryFlag :: Gen a -> Gen (Flag a)
108+
arbitraryFlag genA =
109+
sized $ \sz ->
110+
case sz of
111+
0 -> pure NoFlag
112+
_ -> frequency [ (1, pure NoFlag)
113+
, (3, Flag <$> genA) ]
114+
115+
-- Instances from Distribution.Simple.InstallDirs
116+
117+
instance Arbitrary PathTemplate where
118+
arbitrary = toPathTemplate <$> arbitraryShortToken
119+
shrink t = [ toPathTemplate s | s <- shrink (show t), not (null s) ]
120+
121+
-- Instances from Distribution.System
122+
123+
instance Arbitrary Arch where
124+
arbitrary = elements knownArches
125+
126+
instance Arbitrary OS where
127+
arbitrary = elements knownOSs
128+
129+
instance Arbitrary Platform where
130+
arbitrary = liftM2 Platform arbitrary arbitrary
131+
132+
-- Instances from Distribution.Types.Dependency
133+
134+
instance Arbitrary Dependency where
135+
arbitrary = Dependency <$> arbitrary <*> arbitrary <*> fmap getNonMEmpty arbitrary
136+
137+
-- Instances from Distribution.Types.GenericPackageDescription
138+
139+
instance Arbitrary FlagName where
140+
arbitrary = mkFlagName <$> flagident
141+
where
142+
flagident = lowercase <$> shortListOf1 5 (elements flagChars)
143+
`suchThat` (("-" /=) . take 1)
144+
flagChars = "-_" ++ ['a'..'z']
145+
146+
-- Instances from Distribution.Types.LibraryName
147+
148+
instance Arbitrary LibraryName where
149+
arbitrary = elements =<< sequenceA [LSubLibName <$> arbitrary, pure LMainLibName]
150+
151+
-- Instances from Distribution.Types.PackageName
152+
153+
instance Arbitrary PackageName where
154+
arbitrary = mkPackageName . intercalate "-" <$> shortListOf1 2 nameComponent
155+
where
156+
nameComponent = shortListOf1 5 (elements packageChars)
157+
`suchThat` (not . all isDigit)
158+
packageChars = filter isAlphaNum ['\0'..'\127']
159+
160+
-- Instances from Distribution.Types.UnqualComponentName
161+
162+
instance Arbitrary UnqualComponentName where
163+
-- same rules as package names
164+
arbitrary = packageNameToUnqualComponentName <$> arbitrary
165+
166+
-- Instances from Distribution.Verbosity
167+
168+
instance Arbitrary Verbosity where
169+
arbitrary = elements [minBound..maxBound]
170+
171+
-- Instances from Distribution.Version
172+
173+
instance Arbitrary Bound where
174+
arbitrary = elements [ExclusiveBound, InclusiveBound]
175+
176+
instance Arbitrary Version where
177+
arbitrary = do
178+
branch <- smallListOf1 $
179+
frequency [(3, return 0)
180+
,(3, return 1)
181+
,(2, return 2)
182+
,(2, return 3)
183+
,(1, return 0xfffd)
184+
,(1, return 0xfffe) -- max fitting into packed W64
185+
,(1, return 0xffff)
186+
,(1, return 0x10000)]
187+
return (mkVersion branch)
188+
where
189+
smallListOf1 = adjustSize (\n -> min 6 (n `div` 3)) . listOf1
190+
191+
shrink ver = [ mkVersion ns | ns <- shrink (versionNumbers ver)
192+
, not (null ns) ]
193+
194+
-- | Generating VersionIntervals
195+
--
196+
-- This is a tad tricky as VersionIntervals is an abstract type, so we first
197+
-- make a local type for generating the internal representation. Then we check
198+
-- that this lets us construct valid 'VersionIntervals'.
199+
--
200+
201+
instance Arbitrary VersionIntervals where
202+
arbitrary = fmap mkVersionIntervals' arbitrary
203+
where
204+
mkVersionIntervals' :: [(Version, Bound)] -> VersionIntervals
205+
mkVersionIntervals' = mkVersionIntervals . go version0
206+
where
207+
go :: Version -> [(Version, Bound)] -> [VersionInterval]
208+
go _ [] = []
209+
go v [(lv, lb)] =
210+
[(LowerBound (addVersion lv v) lb, NoUpperBound)]
211+
go v ((lv, lb) : (uv, ub) : rest) =
212+
(LowerBound lv' lb, UpperBound uv' ub) : go uv' rest
213+
where
214+
lv' = addVersion v lv
215+
uv' = addVersion lv' uv
216+
217+
addVersion :: Version -> Version -> Version
218+
addVersion xs ys = mkVersion $ z (versionNumbers xs) (versionNumbers ys)
219+
where
220+
z [] ys' = ys'
221+
z xs' [] = xs'
222+
z (x : xs') (y : ys') = x + y : z xs' ys'
223+
224+
instance Arbitrary VersionRange where
225+
arbitrary = sized verRangeExp
226+
where
227+
verRangeExp n = frequency $
228+
[ (2, return anyVersion)
229+
, (1, liftM thisVersion arbitrary)
230+
, (1, liftM laterVersion arbitrary)
231+
, (1, liftM orLaterVersion arbitrary)
232+
, (1, liftM orLaterVersion' arbitrary)
233+
, (1, liftM earlierVersion arbitrary)
234+
, (1, liftM orEarlierVersion arbitrary)
235+
, (1, liftM orEarlierVersion' arbitrary)
236+
, (1, liftM withinVersion arbitrary)
237+
, (1, liftM majorBoundVersion arbitrary)
238+
, (2, liftM VersionRangeParens arbitrary)
239+
] ++ if n == 0 then [] else
240+
[ (2, liftM2 unionVersionRanges verRangeExp2 verRangeExp2)
241+
, (2, liftM2 intersectVersionRanges verRangeExp2 verRangeExp2)
242+
]
243+
where
244+
verRangeExp2 = verRangeExp (n `div` 2)
245+
246+
orLaterVersion' v =
247+
unionVersionRanges (LaterVersion v) (ThisVersion v)
248+
orEarlierVersion' v =
249+
unionVersionRanges (EarlierVersion v) (ThisVersion v)
250+
251+
shrink AnyVersion = []
252+
shrink (ThisVersion v) = map ThisVersion (shrink v)
253+
shrink (LaterVersion v) = map LaterVersion (shrink v)
254+
shrink (EarlierVersion v) = map EarlierVersion (shrink v)
255+
shrink (OrLaterVersion v) = LaterVersion v : map OrLaterVersion (shrink v)
256+
shrink (OrEarlierVersion v) = EarlierVersion v : map OrEarlierVersion (shrink v)
257+
shrink (WildcardVersion v) = map WildcardVersion ( shrink v)
258+
shrink (MajorBoundVersion v) = map MajorBoundVersion (shrink v)
259+
shrink (VersionRangeParens vr) = vr : map VersionRangeParens (shrink vr)
260+
shrink (UnionVersionRanges a b) = a : b : map (uncurry UnionVersionRanges) (shrink (a, b))
261+
shrink (IntersectVersionRanges a b) = a : b : map (uncurry IntersectVersionRanges) (shrink (a, b))
262+
263+
-- Instances from Distribution.SPDX
264+
265+
instance Arbitrary LicenseId where
266+
arbitrary = elements $ licenseIdList LicenseListVersion_3_2
267+
268+
instance Arbitrary LicenseExceptionId where
269+
arbitrary = elements $ licenseExceptionIdList LicenseListVersion_3_2
270+
271+
instance Arbitrary LicenseExpression where
272+
arbitrary = sized arb
273+
where
274+
arb n
275+
| n <= 0 = ELicense <$> arbitrary <*> pure Nothing
276+
| otherwise = oneof
277+
[ ELicense <$> arbitrary <*> arbitrary
278+
, EAnd <$> arbA <*> arbB
279+
, EOr <$> arbA <*> arbB
280+
]
281+
where
282+
m = n `div` 2
283+
arbA = arb m
284+
arbB = arb (n - m)
285+
286+
shrink (EAnd a b) = a : b : map (uncurry EAnd) (shrink (a, b))
287+
shrink (EOr a b) = a : b : map (uncurry EOr) (shrink (a, b))
288+
shrink _ = []
289+
290+
instance Arbitrary LicenseRef where
291+
arbitrary = mkLicenseRef' <$> ids' <*> ids
292+
where
293+
ids = listOf1 $ elements $ ['a'..'z'] ++ ['A' .. 'Z'] ++ ['0'..'9'] ++ "_-"
294+
ids' = oneof [ pure Nothing, Just <$> ids ]
295+
296+
instance Arbitrary SimpleLicenseExpression where
297+
arbitrary = oneof
298+
[ ELicenseId <$> arbitrary
299+
, ELicenseIdPlus <$> arbitrary
300+
, ELicenseRef <$> arbitrary
301+
]

0 commit comments

Comments
 (0)