Skip to content

Commit 037fb31

Browse files
authored
Use DeriveAnyClass (#2162)
* Enable DeriveAnyClass * Use `deriving anyclass` * stylish-haskell.yaml: language_extensions: DeriveAnyClass
1 parent 7b87490 commit 037fb31

File tree

143 files changed

+1087
-2571
lines changed

Some content is hidden

Large Commits have some content hidden by default. Use the searchbox below for content that may be hidden.

143 files changed

+1087
-2571
lines changed

.stylish-haskell.yaml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -238,6 +238,7 @@ language_extensions:
238238
- ConstraintKinds
239239
- DataKinds
240240
- DefaultSignatures
241+
- DeriveAnyClass
241242
- DeriveDataTypeable
242243
- DeriveFoldable
243244
- DeriveFunctor

kore/package.yaml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -103,6 +103,7 @@ default-extensions:
103103
- ConstraintKinds
104104
- DataKinds
105105
- DefaultSignatures
106+
- DeriveAnyClass
106107
- DeriveDataTypeable
107108
- DeriveFoldable
108109
- DeriveFunctor

kore/src/Control/Monad/Counter.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -58,14 +58,14 @@ type Counter = CounterT Monad.Identity.Identity
5858
-}
5959
newtype CounterT m a =
6060
CounterT { getCounterT :: Monad.State.Strict.StateT Natural m a }
61-
deriving (Alternative, Applicative, Functor, Monad, MonadPlus, MonadTrans)
61+
deriving newtype (Functor, Applicative, Monad)
62+
deriving newtype (Alternative, MonadPlus)
63+
deriving newtype (MonadTrans, MonadState Natural)
6264

6365
instance Monad m => MonadCounter (CounterT m) where
6466
increment = CounterT incrementState
6567
{-# INLINE increment #-}
6668

67-
deriving instance Monad m => MonadState Natural (CounterT m)
68-
6969
instance MonadIO m => MonadIO (CounterT m) where
7070
liftIO = CounterT . liftIO
7171
{-# INLINE liftIO #-}

kore/src/Data/Sup.hs

Lines changed: 6 additions & 9 deletions
Original file line numberDiff line numberDiff line change
@@ -34,7 +34,12 @@ If @a@ already has a least upper bound, 'Sup' is greater than that bound.
3434
data Sup a
3535
= Element !a
3636
| Sup -- ^ least upper bound (supremum)
37-
deriving (Data, Functor, GHC.Generic, Read, Show, Typeable)
37+
deriving (Read, Show)
38+
deriving (Data, Typeable)
39+
deriving (Functor)
40+
deriving (GHC.Generic)
41+
deriving anyclass (Hashable, NFData)
42+
deriving anyclass (SOP.Generic, SOP.HasDatatypeInfo)
3843

3944
instance Eq a => Eq (Sup a) where
4045
(==) Sup = \case { Sup -> True ; _ -> False }
@@ -44,14 +49,6 @@ instance Ord a => Ord (Sup a) where
4449
compare Sup = \case { Sup -> EQ ; _ -> GT }
4550
compare (Element a) = \case { Element b -> compare a b; Sup -> LT }
4651

47-
instance Hashable a => Hashable (Sup a)
48-
49-
instance NFData a => NFData (Sup a)
50-
51-
instance SOP.Generic (Sup a)
52-
53-
instance SOP.HasDatatypeInfo (Sup a)
54-
5552
-- | 'Sup' is the annihilator of 'Element'.
5653
instance Ord a => Semigroup (Sup a) where
5754
(<>) a b = max <$> a <*> b

kore/src/Debug.hs

Lines changed: 2 additions & 8 deletions
Original file line numberDiff line numberDiff line change
@@ -377,14 +377,8 @@ only requires some instances to be derived:
377377
378378
> data DataType = ...
379379
> deriving (GHC.Generics.Generic)
380-
>
381-
> instance Generics.SOP.Generic DataType
382-
>
383-
> instance Generics.SOP.HasDatatypeInfo DataType
384-
>
385-
> instance Debug DataType
386-
>
387-
> instance Diff DataType
380+
> deriving anyclass (SOP.Generic, SOP.HasDatatypeInfo)
381+
> deriving anyclass (Debug, Diff)
388382
389383
-}
390384
class Diff a where

kore/src/Kore/ASTVerifier/PatternVerifier/PatternVerifier.hs

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -75,7 +75,7 @@ newtype DeclaredVariables =
7575
(SomeVariableName VariableName)
7676
(SomeVariable VariableName)
7777
}
78-
deriving (Monoid, Semigroup)
78+
deriving newtype (Monoid, Semigroup)
7979

8080
emptyDeclaredVariables :: DeclaredVariables
8181
emptyDeclaredVariables = mempty
@@ -131,11 +131,11 @@ verifiedModuleContext verifiedModule =
131131
newtype PatternVerifier a =
132132
PatternVerifier
133133
{ getPatternVerifier :: ReaderT Context (Either (Error VerifyError)) a }
134-
deriving (Applicative, Functor, Monad)
134+
deriving newtype (Applicative, Functor, Monad)
135+
deriving newtype (MonadReader Context)
135136

136-
deriving instance MonadReader Context PatternVerifier
137-
138-
deriving instance e ~ VerifyError => MonadError (Error e) PatternVerifier
137+
deriving newtype
138+
instance e ~ VerifyError => MonadError (Error e) PatternVerifier
139139

140140
runPatternVerifier
141141
:: Context

kore/src/Kore/ASTVerifier/Verifier.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -78,13 +78,13 @@ newtype Verifier a =
7878
:: RWST VerifierContext () VerifierState
7979
(Either (Error VerifyError)) a
8080
}
81-
deriving (Functor, Applicative, Monad)
81+
deriving newtype (Functor, Applicative, Monad)
8282

83-
deriving instance MonadReader VerifierContext Verifier
83+
deriving newtype instance MonadReader VerifierContext Verifier
8484

85-
deriving instance MonadState VerifierState Verifier
85+
deriving newtype instance MonadState VerifierState Verifier
8686

87-
deriving instance MonadError (Error VerifyError) Verifier
87+
deriving newtype instance MonadError (Error VerifyError) Verifier
8888

8989
runVerifier
9090
:: Verifier a

kore/src/Kore/Attribute/Assoc.hs

Lines changed: 5 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -22,17 +22,11 @@ import Kore.Debug
2222
{- | @Assoc@ represents the @assoc@ attribute for axioms.
2323
-}
2424
newtype Assoc = Assoc { isAssoc :: Bool }
25-
deriving (Eq, GHC.Generic, Ord, Show)
26-
27-
instance SOP.Generic Assoc
28-
29-
instance SOP.HasDatatypeInfo Assoc
30-
31-
instance Debug Assoc
32-
33-
instance Diff Assoc
34-
35-
instance NFData Assoc
25+
deriving (Eq, Ord, Show)
26+
deriving (GHC.Generic)
27+
deriving anyclass (Hashable, NFData)
28+
deriving anyclass (SOP.Generic, SOP.HasDatatypeInfo)
29+
deriving anyclass (Debug, Diff)
3630

3731
instance Default Assoc where
3832
def = Assoc False

kore/src/Kore/Attribute/Attributes.hs

Lines changed: 6 additions & 17 deletions
Original file line numberDiff line numberDiff line change
@@ -81,23 +81,12 @@ It is parameterized by the types of Patterns, @pat@.
8181

8282
newtype Attributes =
8383
Attributes { getAttributes :: [AttributePattern] }
84-
deriving (Eq, Ord, GHC.Generic, Show)
85-
86-
instance Hashable Attributes
87-
88-
instance NFData Attributes
89-
90-
instance SOP.Generic Attributes
91-
92-
instance SOP.HasDatatypeInfo Attributes
93-
94-
instance Debug Attributes
95-
96-
instance Diff Attributes
97-
98-
deriving instance Semigroup Attributes
99-
100-
deriving instance Monoid Attributes
84+
deriving (Eq, Ord, Show)
85+
deriving (GHC.Generic)
86+
deriving anyclass (Hashable, NFData)
87+
deriving anyclass (SOP.Generic, SOP.HasDatatypeInfo)
88+
deriving anyclass (Debug, Diff)
89+
deriving newtype (Semigroup, Monoid)
10190

10291
instance Unparse Attributes where
10392
unparse = attributes . getAttributes

kore/src/Kore/Attribute/Axiom.hs

Lines changed: 5 additions & 14 deletions
Original file line numberDiff line numberDiff line change
@@ -139,19 +139,11 @@ data Axiom symbol variable =
139139
, owise :: !Owise
140140
-- ^ This is an owise evaluation rule.
141141
}
142-
deriving (Eq, GHC.Generic, Ord, Show)
143-
144-
instance SOP.Generic (Axiom symbol variable)
145-
146-
instance SOP.HasDatatypeInfo (Axiom symbol variable)
147-
148-
instance (Debug symbol, Debug variable) => Debug (Axiom symbol variable)
149-
150-
instance
151-
(Debug symbol, Debug variable, Diff symbol, Diff variable)
152-
=> Diff (Axiom symbol variable)
153-
154-
instance (NFData symbol, NFData variable) => NFData (Axiom symbol variable)
142+
deriving (Eq, Ord, Show)
143+
deriving (GHC.Generic)
144+
deriving anyclass (NFData)
145+
deriving anyclass (SOP.Generic, SOP.HasDatatypeInfo)
146+
deriving anyclass (Debug, Diff)
155147

156148
instance Default (Axiom symbol variable) where
157149
def =
@@ -330,4 +322,3 @@ getPriorityOfAxiom
330322
<> show errorCase
331323
<> " Please report this error."
332324
)
333-

0 commit comments

Comments
 (0)