Skip to content

Commit 8ac04b7

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 haskell#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 8ac04b7

File tree

16 files changed

+518
-362
lines changed

16 files changed

+518
-362
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: 300 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,300 @@
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.PackageVersionConstraint
58+
( PackageVersionConstraint (..)
59+
)
60+
import Distribution.Types.UnqualComponentName
61+
( UnqualComponentName
62+
, packageNameToUnqualComponentName
63+
)
64+
import Distribution.Verbosity
65+
( Verbosity
66+
)
67+
import Distribution.Version
68+
( Bound (..)
69+
, LowerBound (..)
70+
, UpperBound (..)
71+
, Version
72+
, VersionInterval
73+
, VersionIntervals
74+
, VersionRange (..)
75+
, anyVersion
76+
, earlierVersion
77+
, intersectVersionRanges
78+
, laterVersion
79+
, majorBoundVersion
80+
, mkVersion
81+
, mkVersionIntervals
82+
, orEarlierVersion
83+
, orLaterVersion
84+
, thisVersion
85+
, unionVersionRanges
86+
, version0
87+
, versionNumbers
88+
, withinVersion
89+
)
90+
import Test.QuickCheck
91+
( Arbitrary ( arbitrary, shrink )
92+
, elements
93+
, frequency
94+
, listOf1
95+
, oneof
96+
, sized
97+
, suchThat
98+
)
99+
100+
import Distribution.Arbitrary.Util
101+
102+
-- Instances from Distribution.Simple.Flag
103+
104+
instance Arbitrary a => Arbitrary (Flag a) where
105+
arbitrary = arbitraryFlag arbitrary
106+
shrink NoFlag = []
107+
shrink (Flag x) = NoFlag : [ Flag x' | x' <- shrink x ]
108+
109+
-- Instances from Distribution.Simple.InstallDirs
110+
111+
instance Arbitrary PathTemplate where
112+
arbitrary = toPathTemplate <$> arbitraryShortToken
113+
shrink t = [ toPathTemplate s | s <- shrink (show t), not (null s) ]
114+
115+
-- Instances from Distribution.System
116+
117+
instance Arbitrary Arch where
118+
arbitrary = elements knownArches
119+
120+
instance Arbitrary OS where
121+
arbitrary = elements knownOSs
122+
123+
instance Arbitrary Platform where
124+
arbitrary = liftM2 Platform arbitrary arbitrary
125+
126+
-- Instances from Distribution.Types.Dependency
127+
128+
instance Arbitrary Dependency where
129+
arbitrary = Dependency <$> arbitrary <*> arbitrary <*> fmap getNonMEmpty arbitrary
130+
131+
-- Instances from Distribution.Types.GenericPackageDescription
132+
133+
instance Arbitrary FlagName where
134+
arbitrary = mkFlagName <$> flagident
135+
where
136+
flagident = lowercase <$> shortListOf1 5 (elements flagChars)
137+
`suchThat` (("-" /=) . take 1)
138+
flagChars = "-_" ++ ['a'..'z']
139+
140+
-- Instances from Distribution.Types.LibraryName
141+
142+
instance Arbitrary LibraryName where
143+
arbitrary = elements =<< sequenceA [LSubLibName <$> arbitrary, pure LMainLibName]
144+
145+
-- Instances from Distribution.Types.PackageName
146+
147+
instance Arbitrary PackageName where
148+
arbitrary = mkPackageName . intercalate "-" <$> shortListOf1 2 nameComponent
149+
where
150+
nameComponent = shortListOf1 5 (elements packageChars)
151+
`suchThat` (not . all isDigit)
152+
packageChars = filter isAlphaNum ['\0'..'\127']
153+
154+
-- Instances from Distribution.Types.PackageVersionConstraint
155+
156+
instance Arbitrary PackageVersionConstraint where
157+
arbitrary = PackageVersionConstraint <$> arbitrary <*> arbitrary
158+
159+
-- Instances from Distribution.Types.UnqualComponentName
160+
161+
instance Arbitrary UnqualComponentName where
162+
-- same rules as package names
163+
arbitrary = packageNameToUnqualComponentName <$> arbitrary
164+
165+
-- Instances from Distribution.Verbosity
166+
167+
instance Arbitrary Verbosity where
168+
arbitrary = elements [minBound..maxBound]
169+
170+
-- Instances from Distribution.Version
171+
172+
instance Arbitrary Bound where
173+
arbitrary = elements [ExclusiveBound, InclusiveBound]
174+
175+
instance Arbitrary Version where
176+
arbitrary = do
177+
branch <- smallListOf1 $
178+
frequency [(3, return 0)
179+
,(3, return 1)
180+
,(2, return 2)
181+
,(2, return 3)
182+
,(1, return 0xfffd)
183+
,(1, return 0xfffe) -- max fitting into packed W64
184+
,(1, return 0xffff)
185+
,(1, return 0x10000)]
186+
return (mkVersion branch)
187+
where
188+
smallListOf1 = adjustSize (\n -> min 6 (n `div` 3)) . listOf1
189+
190+
shrink ver = [ mkVersion ns | ns <- shrink (versionNumbers ver)
191+
, not (null ns) ]
192+
193+
-- | Generating VersionIntervals
194+
--
195+
-- This is a tad tricky as VersionIntervals is an abstract type, so we first
196+
-- make a local type for generating the internal representation. Then we check
197+
-- that this lets us construct valid 'VersionIntervals'.
198+
--
199+
200+
instance Arbitrary VersionIntervals where
201+
arbitrary = fmap mkVersionIntervals' arbitrary
202+
where
203+
mkVersionIntervals' :: [(Version, Bound)] -> VersionIntervals
204+
mkVersionIntervals' = mkVersionIntervals . go version0
205+
where
206+
go :: Version -> [(Version, Bound)] -> [VersionInterval]
207+
go _ [] = []
208+
go v [(lv, lb)] =
209+
[(LowerBound (addVersion lv v) lb, NoUpperBound)]
210+
go v ((lv, lb) : (uv, ub) : rest) =
211+
(LowerBound lv' lb, UpperBound uv' ub) : go uv' rest
212+
where
213+
lv' = addVersion v lv
214+
uv' = addVersion lv' uv
215+
216+
addVersion :: Version -> Version -> Version
217+
addVersion xs ys = mkVersion $ z (versionNumbers xs) (versionNumbers ys)
218+
where
219+
z [] ys' = ys'
220+
z xs' [] = xs'
221+
z (x : xs') (y : ys') = x + y : z xs' ys'
222+
223+
instance Arbitrary VersionRange where
224+
arbitrary = sized verRangeExp
225+
where
226+
verRangeExp n = frequency $
227+
[ (2, return anyVersion)
228+
, (1, liftM thisVersion arbitrary)
229+
, (1, liftM laterVersion arbitrary)
230+
, (1, liftM orLaterVersion arbitrary)
231+
, (1, liftM orLaterVersion' arbitrary)
232+
, (1, liftM earlierVersion arbitrary)
233+
, (1, liftM orEarlierVersion arbitrary)
234+
, (1, liftM orEarlierVersion' arbitrary)
235+
, (1, liftM withinVersion arbitrary)
236+
, (1, liftM majorBoundVersion arbitrary)
237+
, (2, liftM VersionRangeParens arbitrary)
238+
] ++ if n == 0 then [] else
239+
[ (2, liftM2 unionVersionRanges verRangeExp2 verRangeExp2)
240+
, (2, liftM2 intersectVersionRanges verRangeExp2 verRangeExp2)
241+
]
242+
where
243+
verRangeExp2 = verRangeExp (n `div` 2)
244+
245+
orLaterVersion' v =
246+
unionVersionRanges (LaterVersion v) (ThisVersion v)
247+
orEarlierVersion' v =
248+
unionVersionRanges (EarlierVersion v) (ThisVersion v)
249+
250+
shrink AnyVersion = []
251+
shrink (ThisVersion v) = map ThisVersion (shrink v)
252+
shrink (LaterVersion v) = map LaterVersion (shrink v)
253+
shrink (EarlierVersion v) = map EarlierVersion (shrink v)
254+
shrink (OrLaterVersion v) = LaterVersion v : map OrLaterVersion (shrink v)
255+
shrink (OrEarlierVersion v) = EarlierVersion v : map OrEarlierVersion (shrink v)
256+
shrink (WildcardVersion v) = map WildcardVersion ( shrink v)
257+
shrink (MajorBoundVersion v) = map MajorBoundVersion (shrink v)
258+
shrink (VersionRangeParens vr) = vr : map VersionRangeParens (shrink vr)
259+
shrink (UnionVersionRanges a b) = a : b : map (uncurry UnionVersionRanges) (shrink (a, b))
260+
shrink (IntersectVersionRanges a b) = a : b : map (uncurry IntersectVersionRanges) (shrink (a, b))
261+
262+
-- Instances from Distribution.SPDX
263+
264+
instance Arbitrary LicenseId where
265+
arbitrary = elements $ licenseIdList LicenseListVersion_3_2
266+
267+
instance Arbitrary LicenseExceptionId where
268+
arbitrary = elements $ licenseExceptionIdList LicenseListVersion_3_2
269+
270+
instance Arbitrary LicenseExpression where
271+
arbitrary = sized arb
272+
where
273+
arb n
274+
| n <= 0 = ELicense <$> arbitrary <*> pure Nothing
275+
| otherwise = oneof
276+
[ ELicense <$> arbitrary <*> arbitrary
277+
, EAnd <$> arbA <*> arbB
278+
, EOr <$> arbA <*> arbB
279+
]
280+
where
281+
m = n `div` 2
282+
arbA = arb m
283+
arbB = arb (n - m)
284+
285+
shrink (EAnd a b) = a : b : map (uncurry EAnd) (shrink (a, b))
286+
shrink (EOr a b) = a : b : map (uncurry EOr) (shrink (a, b))
287+
shrink _ = []
288+
289+
instance Arbitrary LicenseRef where
290+
arbitrary = mkLicenseRef' <$> ids' <*> ids
291+
where
292+
ids = listOf1 $ elements $ ['a'..'z'] ++ ['A' .. 'Z'] ++ ['0'..'9'] ++ "_-"
293+
ids' = oneof [ pure Nothing, Just <$> ids ]
294+
295+
instance Arbitrary SimpleLicenseExpression where
296+
arbitrary = oneof
297+
[ ELicenseId <$> arbitrary
298+
, ELicenseIdPlus <$> arbitrary
299+
, ELicenseRef <$> arbitrary
300+
]

0 commit comments

Comments
 (0)