Skip to content

Commit

Permalink
Get rid of 'instance forall', not supported by hugs.
Browse files Browse the repository at this point in the history
  • Loading branch information
augustss committed Jan 19, 2025
1 parent c050cd0 commit 56be300
Show file tree
Hide file tree
Showing 21 changed files with 3,546 additions and 3,545 deletions.
6,885 changes: 3,443 additions & 3,442 deletions generated/mhs.c

Large diffs are not rendered by default.

6 changes: 3 additions & 3 deletions lib/Control/Monad.hs
Original file line number Diff line number Diff line change
Expand Up @@ -186,14 +186,14 @@ ap f a = do

-----

instance forall a . Functor ((->) a) where
instance Functor ((->) a) where
fmap = (.)

instance forall a . Applicative ((->) a) where
instance Applicative ((->) a) where
pure = const
f <*> g = \ a -> f a (g a)

instance forall a . Monad ((->) a) where
instance Monad ((->) a) where
x >>= y = \ z -> y (x z) z

instance Monad Dual where
Expand Down
10 changes: 5 additions & 5 deletions lib/Data/Complex.hs
Original file line number Diff line number Diff line change
Expand Up @@ -6,10 +6,10 @@ infix 6 :+
data Complex a = !a :+ !a
deriving(Typeable)

instance forall a . Eq a => Eq (Complex a) where
instance Eq a => Eq (Complex a) where
(x :+ y) == (x' :+ y') = x == x' && y == y' -- parser bug

instance forall a . Show a => Show (Complex a) where
instance Show a => Show (Complex a) where
show (x :+ y) = show x ++ " :+ " ++ show y

realPart :: forall a . Complex a -> a
Expand Down Expand Up @@ -46,7 +46,7 @@ phase (x:+y) | x==0 && y==0 = 0
| otherwise = atan2 y x


instance forall a . (RealFloat a) => Num (Complex a) where
instance (RealFloat a) => Num (Complex a) where
(x:+y) + (x':+y') = (x+x') :+ (y+y')
(x:+y) - (x':+y') = (x-x') :+ (y-y')
(x:+y) * (x':+y') = (x*x'-y*y') :+ (x*y'+y*x')
Expand All @@ -57,7 +57,7 @@ instance forall a . (RealFloat a) => Num (Complex a) where
| otherwise = x/r :+ y/r where r = magnitude z
fromInteger n = fromInteger n :+ 0

instance forall a . (RealFloat a) => Fractional (Complex a) where
instance (RealFloat a) => Fractional (Complex a) where
(x:+y) / (x':+y') = (x*x''+y*y'') / d :+ (y*x''-x*y'') / d
where x'' = scaleFloat k x'
y'' = scaleFloat k y'
Expand All @@ -66,7 +66,7 @@ instance forall a . (RealFloat a) => Fractional (Complex a) where

fromRational a = fromRational a :+ 0

instance forall a . (RealFloat a) => Floating (Complex a) where
instance (RealFloat a) => Floating (Complex a) where
pi = pi :+ 0
exp (x:+y) = expx * cos y :+ expx * sin y
where expx = exp x
Expand Down
2 changes: 1 addition & 1 deletion lib/Data/Constraint.hs
Original file line number Diff line number Diff line change
Expand Up @@ -10,7 +10,7 @@ import Text.Show
type Dict :: Constraint -> Type
data Dict c = c => Dict

instance forall c . Show (Dict c) where
instance Show (Dict c) where
showsPrec _ Dict = showString "Dict"

withDict :: forall c r . Dict c -> (c => r) -> r
Expand Down
8 changes: 4 additions & 4 deletions lib/Data/Either.hs
Original file line number Diff line number Diff line change
Expand Up @@ -28,20 +28,20 @@ isRight :: forall a b . Either a b -> Bool
isRight (Left _) = False
isRight (Right _) = True

instance forall a b . (Show a, Show b) => Show (Either a b) where
instance (Show a, Show b) => Show (Either a b) where
showsPrec p (Left a) = showParen (p>=appPrec1) (showString "Left " . showsPrec appPrec1 a)
showsPrec p (Right b) = showParen (p>=appPrec1) (showString "Right " . showsPrec appPrec1 b)

instance forall a . Functor (Either a) where
instance Functor (Either a) where
fmap _ (Left a) = Left a
fmap f (Right b) = Right (f b)

instance forall a . Applicative (Either a) where
instance Applicative (Either a) where
pure b = Right b
Right f <*> Right x = Right (f x)
Right _ <*> Left a = Left a
Left a <*> _ = Left a

instance forall a . Monad (Either a) where
instance Monad (Either a) where
Right b >>= k = k b
Left a >>= _ = Left a
2 changes: 1 addition & 1 deletion lib/Data/Fixed.hs
Original file line number Diff line number Diff line change
Expand Up @@ -84,7 +84,7 @@ type HasResolution :: forall k . k -> Constraint
class HasResolution a where
resolution :: p a -> Integer

instance forall n . KnownNat n => HasResolution n where
instance KnownNat n => HasResolution n where
resolution _ = natVal (Proxy :: Proxy n)

withType :: (Proxy a -> f a) -> f a
Expand Down
4 changes: 2 additions & 2 deletions lib/Data/Foldable.hs
Original file line number Diff line number Diff line change
Expand Up @@ -163,7 +163,7 @@ instance Foldable [] where
sum = List.sum
toList = id

instance forall a . Foldable (Either a) where
instance Foldable (Either a) where
foldMap _ (Left _) = mempty
foldMap f (Right y) = f y

Expand All @@ -181,7 +181,7 @@ instance Foldable Proxy where
instance Foldable Identity where
foldMap f (Identity a) = f a

instance forall m . Foldable (Const m) where
instance Foldable (Const m) where
foldMap _ _ = mempty

{-
Expand Down
2 changes: 1 addition & 1 deletion lib/Data/IORef.hs
Original file line number Diff line number Diff line change
Expand Up @@ -14,7 +14,7 @@ import {-# SOURCE #-} Data.Typeable
newtype IORef a = R (IOArray a)
deriving (Typeable)

instance forall a . Eq (IORef a) where
instance Eq (IORef a) where
R x == R y = primArrEQ x y

newIORef :: forall a . a -> IO (IORef a)
Expand Down
10 changes: 5 additions & 5 deletions lib/Data/List.hs
Original file line number Diff line number Diff line change
Expand Up @@ -47,12 +47,12 @@ import Data.Tuple
--import Text.Read
import Text.Show

instance {-# OVERLAPPABLE #-} forall a . Eq a => Eq [a] where
instance {-# OVERLAPPABLE #-} Eq a => Eq [a] where
[] == [] = True
(x:xs) == (y:ys) = x == y && xs == ys
_ == _ = False

instance forall a . Ord a => Ord [a] where
instance Ord a => Ord [a] where
[] <= _ = True
(_:_) <= [] = False
(x:xs) <= (y:ys) = x < y || x == y && xs <= ys
Expand All @@ -64,17 +64,17 @@ instance Applicative [] where
pure a = [a]
fs <*> xs = concatMap (\ f -> map (\ x -> f x) xs) fs

instance forall a . Show a => Show [a] where
instance Show a => Show [a] where
showsPrec _ = showList

instance Alternative [] where
empty = []
(<|>) = (++)

instance forall a . Semigroup [a] where
instance Semigroup [a] where
(<>) = (++)

instance forall a . Monoid [a] where
instance Monoid [a] where
mempty = []
mconcat = concat

Expand Down
10 changes: 5 additions & 5 deletions lib/Data/Maybe.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,18 +19,18 @@ import Data.Monoid.Internal
import Data.Ord
import Text.Show

instance forall a . Eq a => Eq (Maybe a) where
instance Eq a => Eq (Maybe a) where
Nothing == Nothing = True
Just x == Just x' = x == x'
_ == _ = False

instance forall a . Ord a => Ord (Maybe a) where
instance Ord a => Ord (Maybe a) where
Nothing `compare` Nothing = EQ
Nothing `compare` Just _ = LT
Just _ `compare` Nothing = GT
Just x `compare` Just y = x `compare` y

instance forall a . (Show a) => Show (Maybe a) where
instance (Show a) => Show (Maybe a) where
showsPrec _ Nothing = showString "Nothing"
showsPrec p (Just a) = showParen (p >= 11) (showString "Just " . showsPrec 11 a)

Expand Down Expand Up @@ -61,12 +61,12 @@ instance Alternative Maybe where
Nothing <|> y = y
x <|> _ = x

instance forall a . Semigroup a => Semigroup (Maybe a) where
instance Semigroup a => Semigroup (Maybe a) where
Nothing <> b = b
a <> Nothing = a
Just a <> Just b = Just (a <> b)

instance forall a . Semigroup a => Monoid (Maybe a) where
instance Semigroup a => Monoid (Maybe a) where
mempty = Nothing

maybe :: forall a r . r -> (a -> r) -> Maybe a -> r
Expand Down
8 changes: 4 additions & 4 deletions lib/Data/Monoid.hs
Original file line number Diff line number Diff line change
Expand Up @@ -21,19 +21,19 @@ import Data.Records

newtype First a = First { getFirst :: Maybe a }

instance forall a . Semigroup (First a) where
instance Semigroup (First a) where
a@(First (Just _)) <> _ = a
First Nothing <> a = a

instance forall a . Monoid (First a) where
instance Monoid (First a) where
mempty = First Nothing


newtype Last a = Last { getLast :: Maybe a }

instance forall a . Semigroup (Last a) where
instance Semigroup (Last a) where
_ <> a@(Last (Just _)) = a
a <> Last Nothing = a

instance forall a . Monoid (Last a) where
instance Monoid (Last a) where
mempty = Last Nothing
4 changes: 2 additions & 2 deletions lib/Data/Proxy.hs
Original file line number Diff line number Diff line change
Expand Up @@ -9,10 +9,10 @@ import Text.Show
type Proxy :: forall (k::Kind) . k -> Type
data Proxy a = Proxy

instance forall a . Show (Proxy a) where
instance Show (Proxy a) where
show _ = "Proxy"

instance forall a . Eq (Proxy a) where
instance Eq (Proxy a) where
_ == _ = True

instance Functor Proxy where
Expand Down
12 changes: 6 additions & 6 deletions lib/Data/Ratio.hs
Original file line number Diff line number Diff line change
Expand Up @@ -54,16 +54,16 @@ instance (Integral a) => Enum (Ratio a) where
enumFromTo = numericEnumFromTo
enumFromThenTo = numericEnumFromThenTo

instance forall a . Eq a => Eq (Ratio a) where
instance Eq a => Eq (Ratio a) where
(x :% y) == (x' :% y') = x == x' && y == y'

instance forall a . (Integral a, Ord a) => Ord (Ratio a) where
instance (Integral a, Ord a) => Ord (Ratio a) where
(x :% y) <= (x' :% y') = x * y' <= x' * y
(x :% y) < (x' :% y') = x * y' < x' * y
(x :% y) >= (x' :% y') = x * y' >= x' * y
(x :% y) > (x' :% y') = x * y' > x' * y

instance forall a . (Integral a, Ord a) => Num (Ratio a) where
instance (Integral a, Ord a) => Num (Ratio a) where
(x:%y) + (x':%y') = reduce (x*y' + x'*y) (y*y')
(x:%y) - (x':%y') = reduce (x*y' - x'*y) (y*y')
(x:%y) * (x':%y') = reduce (x * x') (y * y')
Expand All @@ -72,20 +72,20 @@ instance forall a . (Integral a, Ord a) => Num (Ratio a) where
signum (x:%_) = signum x :% 1
fromInteger x = fromInteger x :% 1

instance forall a . (Integral a, Ord a) => Fractional (Ratio a) where
instance (Integral a, Ord a) => Fractional (Ratio a) where
(x:%y) / (x':%y') = reduce (x*y') (y*x')
recip (x:%y)
| x < 0 = (-y) :% (-x)
| otherwise = y :% x
fromRational (x:%y) = fromInteger x % fromInteger y

instance forall a . (Show a) => Show (Ratio a) where
instance (Show a) => Show (Ratio a) where
showsPrec p (x:%y) = showParen (p > 7) $
showsPrec 8 x .
showString " % " .
showsPrec 8 y

instance forall a . (Integral a, Ord a) => Real (Ratio a) where
instance (Integral a, Ord a) => Real (Ratio a) where
toRational (x :% y) = toInteger x :% toInteger y

rationalInfinity :: Rational
Expand Down
4 changes: 2 additions & 2 deletions lib/Data/Traversable.hs
Original file line number Diff line number Diff line change
Expand Up @@ -70,7 +70,7 @@ instance Traversable [] where
traverse f = List.foldr cons_f (pure [])
where cons_f x ys = liftA2 (:) (f x) ys

instance forall a . Traversable (Either a) where
instance Traversable (Either a) where
traverse _ (Left x) = pure (Left x)
traverse f (Right y) = Right <$> f y

Expand All @@ -80,7 +80,7 @@ instance Traversable Identity where
instance Traversable Proxy where
traverse _ _ = pure Proxy

instance forall m . Traversable (Const m) where
instance Traversable (Const m) where
traverse _ (Const m) = pure $ Const m

{-
Expand Down
Loading

0 comments on commit 56be300

Please sign in to comment.