@@ -8,8 +8,7 @@ License : NCSA
88{-# LANGUAGE UndecidableInstances #-}
99
1010module Kore.Internal.TermLike.TermLike
11- ( Evaluated (.. )
12- , TermLike (.. )
11+ ( TermLike (.. )
1312 , TermLikeF (.. )
1413 , retractKey
1514 , extractAttributes
@@ -120,34 +119,6 @@ import Kore.Variables.Binding
120119import qualified Pretty
121120import qualified SQL
122121
123- {- | @Evaluated@ wraps patterns which are fully evaluated.
124-
125- Fully-evaluated patterns will not be simplified further because no progress
126- could be made.
127-
128- -}
129- newtype Evaluated child = Evaluated { getEvaluated :: child }
130- deriving (Eq , Ord , Show )
131- deriving (Foldable , Functor , Traversable )
132- deriving (GHC.Generic )
133- deriving anyclass (Hashable , NFData )
134- deriving anyclass (SOP.Generic , SOP.HasDatatypeInfo )
135- deriving anyclass (Debug , Diff )
136-
137- instance Unparse child => Unparse (Evaluated child ) where
138- unparse evaluated =
139- Pretty. vsep [" /* evaluated: */" , Unparser. unparseGeneric evaluated]
140- unparse2 evaluated =
141- Pretty. vsep [" /* evaluated: */" , Unparser. unparse2Generic evaluated]
142-
143- instance Synthetic syn Evaluated where
144- synthetic = getEvaluated
145- {-# INLINE synthetic #-}
146-
147- instance {-# OVERLAPS #-} Synthetic Pattern. Simplified Evaluated where
148- synthetic = const Pattern. fullySimplified
149- {-# INLINE synthetic #-}
150-
151122{- | 'TermLikeF' is the 'Base' functor of internal term-like patterns.
152123
153124-}
@@ -174,7 +145,6 @@ data TermLikeF variable child
174145 | RewritesF ! (Rewrites Sort child )
175146 | TopF ! (Top Sort child )
176147 | InhabitantF ! (Inhabitant child )
177- | EvaluatedF ! (Evaluated child )
178148 | StringLiteralF ! (Const StringLiteral child )
179149 | InternalBoolF ! (Const InternalBool child )
180150 | InternalBytesF ! (Const InternalBytes child )
@@ -226,7 +196,6 @@ instance
226196 RewritesF rewrites -> synthetic rewrites
227197 TopF top -> synthetic top
228198 InhabitantF inhabitant -> synthetic inhabitant
229- EvaluatedF evaluated -> synthetic evaluated
230199 StringLiteralF stringLiteral -> synthetic stringLiteral
231200 InternalBoolF internalBool -> synthetic internalBool
232201 InternalBytesF internalBytes -> synthetic internalBytes
@@ -264,7 +233,6 @@ instance Synthetic Sort (TermLikeF variable) where
264233 RewritesF rewrites -> synthetic rewrites
265234 TopF top -> synthetic top
266235 InhabitantF inhabitant -> synthetic inhabitant
267- EvaluatedF evaluated -> synthetic evaluated
268236 StringLiteralF stringLiteral -> synthetic stringLiteral
269237 InternalBoolF internalBool -> synthetic internalBool
270238 InternalBytesF internalBytes -> synthetic internalBytes
@@ -302,7 +270,6 @@ instance Synthetic Pattern.Functional (TermLikeF variable) where
302270 RewritesF rewrites -> synthetic rewrites
303271 TopF top -> synthetic top
304272 InhabitantF inhabitant -> synthetic inhabitant
305- EvaluatedF evaluated -> synthetic evaluated
306273 StringLiteralF stringLiteral -> synthetic stringLiteral
307274 InternalBoolF internalBool -> synthetic internalBool
308275 InternalBytesF internalBytes -> synthetic internalBytes
@@ -340,7 +307,6 @@ instance Synthetic Pattern.Function (TermLikeF variable) where
340307 RewritesF rewrites -> synthetic rewrites
341308 TopF top -> synthetic top
342309 InhabitantF inhabitant -> synthetic inhabitant
343- EvaluatedF evaluated -> synthetic evaluated
344310 StringLiteralF stringLiteral -> synthetic stringLiteral
345311 InternalBoolF internalBool -> synthetic internalBool
346312 InternalBytesF internalBytes -> synthetic internalBytes
@@ -378,7 +344,6 @@ instance Synthetic Pattern.Defined (TermLikeF variable) where
378344 RewritesF rewrites -> synthetic rewrites
379345 TopF top -> synthetic top
380346 InhabitantF inhabitant -> synthetic inhabitant
381- EvaluatedF evaluated -> synthetic evaluated
382347 StringLiteralF stringLiteral -> synthetic stringLiteral
383348 InternalBoolF internalBool -> synthetic internalBool
384349 InternalBytesF internalBytes -> synthetic internalBytes
@@ -416,7 +381,6 @@ instance Synthetic Pattern.Simplified (TermLikeF variable) where
416381 RewritesF rewrites -> synthetic rewrites
417382 TopF top -> synthetic top
418383 InhabitantF inhabitant -> synthetic inhabitant
419- EvaluatedF evaluated -> synthetic evaluated
420384 StringLiteralF stringLiteral -> synthetic stringLiteral
421385 InternalBoolF internalBool -> synthetic internalBool
422386 InternalBytesF internalBytes -> synthetic internalBytes
@@ -454,7 +418,6 @@ instance Synthetic Pattern.ConstructorLike (TermLikeF variable) where
454418 RewritesF rewrites -> synthetic rewrites
455419 TopF top -> synthetic top
456420 InhabitantF inhabitant -> synthetic inhabitant
457- EvaluatedF evaluated -> synthetic evaluated
458421 StringLiteralF stringLiteral -> synthetic stringLiteral
459422 InternalBoolF internalBool -> synthetic internalBool
460423 InternalBytesF internalBytes -> synthetic internalBytes
@@ -752,8 +715,6 @@ instance
752715 TopF Top { topSort } -> locationFromAst topSort
753716 VariableF (Const variable) -> locationFromAst variable
754717 InhabitantF Inhabitant { inhSort } -> locationFromAst inhSort
755- EvaluatedF Evaluated { getEvaluated } ->
756- locationFromAst getEvaluated
757718 InjF Inj { injChild } -> locationFromAst injChild
758719 SignednessF (Const signedness) -> locationFromAst signedness
759720 EndiannessF (Const endianness) -> locationFromAst endianness
@@ -821,7 +782,6 @@ traverseVariablesF adj =
821782 InternalSetF setP -> pure (InternalSetF setP)
822783 TopF topP -> pure (TopF topP)
823784 InhabitantF s -> pure (InhabitantF s)
824- EvaluatedF childP -> pure (EvaluatedF childP)
825785 EndiannessF endianness -> pure (EndiannessF endianness)
826786 SignednessF signedness -> pure (SignednessF signedness)
827787 InjF inj -> pure (InjF inj)
0 commit comments