Skip to content

Commit

Permalink
Add .ghc.environment files to .gitignore
Browse files Browse the repository at this point in the history
  • Loading branch information
phadej committed Oct 14, 2017
1 parent 980857d commit 30f4a60
Show file tree
Hide file tree
Showing 4 changed files with 61 additions and 13 deletions.
1 change: 1 addition & 0 deletions .gitignore
Original file line number Diff line number Diff line change
@@ -1,5 +1,6 @@
/dist/
/dist-newstyle/
.ghc.environment.*
*.hi
*.o
*~
Expand Down
6 changes: 1 addition & 5 deletions QuickCheck.cabal
Original file line number Diff line number Diff line change
Expand Up @@ -102,10 +102,6 @@ library
if impl (ghc < 7.4)
cpp-options: -DNO_SAFE_HASKELL

-- Typeable
if impl(ghc < 7.10)
cpp-options: -DMANUAL_TYPEABLE

-- Use tf-random on newer GHCs.
if impl(ghc) && !impl(haste)
Build-depends: tf-random >= 0.4
Expand All @@ -122,7 +118,7 @@ library
if !impl(ghc)
-- If your Haskell compiler can cope without some of these, please
-- send a message to the QuickCheck mailing list!
cpp-options: -DNO_TIMEOUT -DNO_NEWTYPE_DERIVING -DNO_GENERICS -DNO_TEMPLATE_HASKELL -DNO_SAFE_HASKELL
cpp-options: -DNO_TIMEOUT -DNO_NEWTYPE_DERIVING -DNO_GENERICS -DNO_TEMPLATE_HASKELL -DNO_SAFE_HASKELL -DNO_TYPEABLE
if !impl(hugs) && !impl(uhc)
cpp-options: -DNO_ST_MONAD -DNO_MULTI_PARAM_TYPE_CLASSES

Expand Down
61 changes: 56 additions & 5 deletions Test/QuickCheck/Modifiers.hs
Original file line number Diff line number Diff line change
Expand Up @@ -8,6 +8,9 @@
#ifndef NO_NEWTYPE_DERIVING
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
#endif
#ifndef NO_TYPEABLE
{-# LANGUAGE DeriveDataTypeable #-}
#endif
-- | Modifiers for test data.
--
-- These types do things such as restricting the kind of test data that can be generated.
Expand Down Expand Up @@ -73,12 +76,19 @@ import Data.List
)
import Data.Ix (Ix)

#ifndef NO_TYPEABLE
import Data.Typeable (Typeable)
#endif

--------------------------------------------------------------------------
-- | @Blind x@: as x, but x does not have to be in the 'Show' class.
newtype Blind a = Blind {getBlind :: a}
deriving ( Eq, Ord
#ifndef NO_NEWTYPE_DERIVING
, Num, Integral, Real, Enum
#endif
#ifndef NO_TYPEABLE
, Typeable
#endif
)

Expand All @@ -99,6 +109,9 @@ newtype Fixed a = Fixed {getFixed :: a}
deriving ( Eq, Ord, Show, Read
#ifndef NO_NEWTYPE_DERIVING
, Num, Integral, Real, Enum
#endif
#ifndef NO_TYPEABLE
, Typeable
#endif
)

Expand All @@ -113,7 +126,11 @@ instance Arbitrary a => Arbitrary (Fixed a) where
--------------------------------------------------------------------------
-- | @Ordered xs@: guarantees that xs is ordered.
newtype OrderedList a = Ordered {getOrdered :: [a]}
deriving ( Eq, Ord, Show, Read )
deriving ( Eq, Ord, Show, Read
#ifndef NO_TYPEABLE
, Typeable
#endif
)

instance Functor OrderedList where
fmap f (Ordered x) = Ordered (map f x)
Expand All @@ -130,7 +147,11 @@ instance (Ord a, Arbitrary a) => Arbitrary (OrderedList a) where
--------------------------------------------------------------------------
-- | @NonEmpty xs@: guarantees that xs is non-empty.
newtype NonEmptyList a = NonEmpty {getNonEmpty :: [a]}
deriving ( Eq, Ord, Show, Read )
deriving ( Eq, Ord, Show, Read
#ifndef NO_TYPEABLE
, Typeable
#endif
)

instance Functor NonEmptyList where
fmap f (NonEmpty x) = NonEmpty (map f x)
Expand All @@ -150,6 +171,9 @@ newtype Positive a = Positive {getPositive :: a}
deriving ( Eq, Ord, Show, Read
#ifndef NO_NEWTYPE_DERIVING
, Enum
#endif
#ifndef NO_TYPEABLE
, Typeable
#endif
)

Expand All @@ -173,6 +197,9 @@ newtype NonZero a = NonZero {getNonZero :: a}
deriving ( Eq, Ord, Show, Read
#ifndef NO_NEWTYPE_DERIVING
, Enum
#endif
#ifndef NO_TYPEABLE
, Typeable
#endif
)

Expand All @@ -190,6 +217,9 @@ newtype NonNegative a = NonNegative {getNonNegative :: a}
deriving ( Eq, Ord, Show, Read
#ifndef NO_NEWTYPE_DERIVING
, Enum
#endif
#ifndef NO_TYPEABLE
, Typeable
#endif
)

Expand Down Expand Up @@ -219,6 +249,9 @@ newtype Large a = Large {getLarge :: a}
deriving ( Eq, Ord, Show, Read
#ifndef NO_NEWTYPE_DERIVING
, Num, Integral, Real, Enum, Ix
#endif
#ifndef NO_TYPEABLE
, Typeable
#endif
)

Expand All @@ -236,6 +269,9 @@ newtype Small a = Small {getSmall :: a}
deriving ( Eq, Ord, Show, Read
#ifndef NO_NEWTYPE_DERIVING
, Num, Integral, Real, Enum, Ix
#endif
#ifndef NO_TYPEABLE
, Typeable
#endif
)

Expand All @@ -252,6 +288,9 @@ newtype Shrink2 a = Shrink2 {getShrink2 :: a}
deriving ( Eq, Ord, Show, Read
#ifndef NO_NEWTYPE_DERIVING
, Num, Integral, Real, Enum
#endif
#ifndef NO_TYPEABLE
, Typeable
#endif
)

Expand Down Expand Up @@ -349,7 +388,11 @@ instance (Arbitrary a, ShrinkState s a) => Arbitrary (Shrinking s a) where
--------------------------------------------------------------------------
-- | @ASCIIString@: generates an ASCII string.
newtype ASCIIString = ASCIIString {getASCIIString :: String}
deriving ( Eq, Ord, Show, Read )
deriving ( Eq, Ord, Show, Read
#ifndef NO_TYPEABLE
, Typeable
#endif
)

instance Arbitrary ASCIIString where
arbitrary = ASCIIString `fmap` listOf arbitraryASCIIChar
Expand All @@ -359,7 +402,11 @@ instance Arbitrary ASCIIString where
-- | @UnicodeString@: generates a unicode String.
-- The string will not contain surrogate pairs.
newtype UnicodeString = UnicodeString {getUnicodeString :: String}
deriving ( Eq, Ord, Show, Read )
deriving ( Eq, Ord, Show, Read
#ifndef NO_TYPEABLE
, Typeable
#endif
)

instance Arbitrary UnicodeString where
arbitrary = UnicodeString `fmap` listOf arbitraryUnicodeChar
Expand All @@ -369,7 +416,11 @@ instance Arbitrary UnicodeString where
-- | @PrintableString@: generates a printable unicode String.
-- The string will not contain surrogate pairs.
newtype PrintableString = PrintableString {getPrintableString :: String}
deriving ( Eq, Ord, Show, Read )
deriving ( Eq, Ord, Show, Read
#ifndef NO_TYPEABLE
, Typeable
#endif
)

instance Arbitrary PrintableString where
arbitrary = PrintableString `fmap` listOf arbitraryPrintableChar
Expand Down
6 changes: 3 additions & 3 deletions Test/QuickCheck/Property.hs
Original file line number Diff line number Diff line change
@@ -1,6 +1,6 @@
-- | Combinators for constructing properties.
{-# LANGUAGE CPP #-}
#ifdef MANUAL_TYPEABLE
#ifndef NO_TYPEABLE
{-# LANGUAGE DeriveDataTypeable #-}
#endif
#ifndef NO_SAFE_HASKELL
Expand Down Expand Up @@ -31,7 +31,7 @@ import Data.Set(Set)
#ifndef NO_DEEPSEQ
import Control.DeepSeq
#endif
#ifdef MANUAL_TYPEABLE
#ifndef NO_TYPEABLE
import Data.Typeable (Typeable)
#endif

Expand Down Expand Up @@ -77,7 +77,7 @@ infixr 1 .||.

-- | The type of properties.
newtype Property = MkProperty { unProperty :: Gen Prop }
#ifdef MANUAL_TYPEABLE
#ifndef NO_TYPEABLE
deriving (Typeable)
#endif

Expand Down

0 comments on commit 30f4a60

Please sign in to comment.