Skip to content

Commit 2dbbaa9

Browse files
ana-pantiliettuegelrv-jenkins
authored
Kore.Syntax: make fields strict, add language strict (#2504)
* Kore.Syntax: make fields strict * Format with fourmolu Co-authored-by: ana-pantilie <[email protected]> Co-authored-by: Thomas Tuegel <[email protected]> Co-authored-by: rv-jenkins <[email protected]>
1 parent b3915d4 commit 2dbbaa9

23 files changed

+74
-29
lines changed

kore/src/Kore/Syntax/And.hs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE Strict #-}
2+
13
{- |
24
Copyright : (c) Runtime Verification, 2019
35
License : NCSA
@@ -26,8 +28,8 @@ This represents the 'andFirst ∧ andSecond' Matching Logic construct.
2628
-}
2729
data And sort child = And
2830
{ andSort :: !sort
29-
, andFirst :: child
30-
, andSecond :: child
31+
, andFirst :: !child
32+
, andSecond :: !child
3133
}
3234
deriving (Eq, Ord, Show)
3335
deriving (Functor, Foldable, Traversable)

kore/src/Kore/Syntax/Application.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE Strict #-}
2+
13
{- |
24
Copyright : (c) Runtime Verification, 2018
35
License : NCSA
@@ -62,7 +64,7 @@ This represents the @σ(φ1, ..., φn)@ symbol patterns in Matching Logic.
6264
-}
6365
data Application head child = Application
6466
{ applicationSymbolOrAlias :: !head
65-
, applicationChildren :: [child]
67+
, applicationChildren :: ![child]
6668
}
6769
deriving (Eq, Ord, Show)
6870
deriving (Functor, Foldable, Traversable)

kore/src/Kore/Syntax/Bottom.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE Strict #-}
2+
13
{- |
24
Copyright : (c) Runtime Verification, 2019
35
License : NCSA

kore/src/Kore/Syntax/Ceil.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE Strict #-}
2+
13
{- |
24
Copyright : (c) Runtime Verification, 2019
35
License : NCSA
@@ -29,7 +31,7 @@ This represents the ⌈ceilPattern⌉ Matching Logic construct.
2931
data Ceil sort child = Ceil
3032
{ ceilOperandSort :: !sort
3133
, ceilResultSort :: !sort
32-
, ceilChild :: child
34+
, ceilChild :: !child
3335
}
3436
deriving (Eq, Ord, Show)
3537
deriving (Functor, Foldable, Traversable)

kore/src/Kore/Syntax/DomainValue.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE Strict #-}
2+
13
{- |
24
Copyright : (c) Runtime Verification, 2019
35
License : NCSA

kore/src/Kore/Syntax/Equals.hs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE Strict #-}
2+
13
{- |
24
Copyright : (c) Runtime Verification, 2019
35
License : NCSA
@@ -30,8 +32,8 @@ Section 9.1.4 (Patterns).
3032
data Equals sort child = Equals
3133
{ equalsOperandSort :: !sort
3234
, equalsResultSort :: !sort
33-
, equalsFirst :: child
34-
, equalsSecond :: child
35+
, equalsFirst :: !child
36+
, equalsSecond :: !child
3537
}
3638
deriving (Eq, Ord, Show)
3739
deriving (Functor, Foldable, Traversable)

kore/src/Kore/Syntax/Exists.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE Strict #-}
2+
13
{- |
24
Copyright : (c) Runtime Verification, 2019
35
License : NCSA
@@ -26,7 +28,7 @@ Section 9.1.4 (Patterns).
2628
data Exists sort variable child = Exists
2729
{ existsSort :: !sort
2830
, existsVariable :: !(ElementVariable variable)
29-
, existsChild :: child
31+
, existsChild :: !child
3032
}
3133
deriving (Eq, Ord, Show)
3234
deriving (Functor, Foldable, Traversable)

kore/src/Kore/Syntax/Floor.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE Strict #-}
2+
13
{- |
24
Copyright : (c) Runtime Verification, 2019
35
License : NCSA
@@ -27,7 +29,7 @@ Section 9.1.4 (Patterns).
2729
data Floor sort child = Floor
2830
{ floorOperandSort :: !sort
2931
, floorResultSort :: !sort
30-
, floorChild :: child
32+
, floorChild :: !child
3133
}
3234
deriving (Eq, Ord, Show)
3335
deriving (Functor, Foldable, Traversable)

kore/src/Kore/Syntax/Forall.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE Strict #-}
2+
13
{- |
24
Copyright : (c) Runtime Verification, 2019
35
License : NCSA
@@ -26,7 +28,7 @@ Section 9.1.4 (Patterns).
2628
data Forall sort variable child = Forall
2729
{ forallSort :: !sort
2830
, forallVariable :: !(ElementVariable variable)
29-
, forallChild :: child
31+
, forallChild :: !child
3032
}
3133
deriving (Eq, Ord, Show)
3234
deriving (Functor, Foldable, Traversable)

kore/src/Kore/Syntax/Id.hs

Lines changed: 6 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE Strict #-}
2+
13
{- |
24
Copyright : (c) Runtime Verification, 2018
35
License : NCSA
@@ -115,7 +117,7 @@ data AstLocation
115117
| AstLocationImplicit
116118
| AstLocationGeneratedVariable
117119
| AstLocationTest
118-
| AstLocationFile FileLocation
120+
| AstLocationFile !FileLocation
119121
| -- | This should not be used and should be eliminated in further releases
120122
AstLocationUnknown
121123
deriving (Eq, Ord, Show)
@@ -149,9 +151,9 @@ prettyPrintAstLocation AstLocationUnknown = "<unknown location>"
149151

150152
-- | 'FileLocation' represents a position in a source file.
151153
data FileLocation = FileLocation
152-
{ fileName :: FilePath
153-
, line :: Int
154-
, column :: Int
154+
{ fileName :: !FilePath
155+
, line :: !Int
156+
, column :: !Int
155157
}
156158
deriving (Eq, Ord, Show)
157159
deriving (GHC.Generic)

kore/src/Kore/Syntax/Iff.hs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE Strict #-}
2+
13
{- |
24
Copyright : (c) Runtime Verification, 2019
35
License : NCSA
@@ -24,8 +26,8 @@ Section 9.1.4 (Patterns).
2426
-}
2527
data Iff sort child = Iff
2628
{ iffSort :: !sort
27-
, iffFirst :: child
28-
, iffSecond :: child
29+
, iffFirst :: !child
30+
, iffSecond :: !child
2931
}
3032
deriving (Eq, Ord, Show)
3133
deriving (Functor, Foldable, Traversable)

kore/src/Kore/Syntax/Implies.hs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE Strict #-}
2+
13
{- |
24
Copyright : (c) Runtime Verification, 2019
35
License : NCSA
@@ -24,8 +26,8 @@ Section 9.1.4 (Patterns).
2426
-}
2527
data Implies sort child = Implies
2628
{ impliesSort :: !sort
27-
, impliesFirst :: child
28-
, impliesSecond :: child
29+
, impliesFirst :: !child
30+
, impliesSecond :: !child
2931
}
3032
deriving (Eq, Ord, Show)
3133
deriving (Functor, Foldable, Traversable)

kore/src/Kore/Syntax/In.hs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE Strict #-}
2+
13
{- |
24
Copyright : (c) Runtime Verification, 2019
35
License : NCSA
@@ -27,8 +29,8 @@ Section 9.1.4 (Patterns).
2729
data In sort child = In
2830
{ inOperandSort :: !sort
2931
, inResultSort :: !sort
30-
, inContainedChild :: child
31-
, inContainingChild :: child
32+
, inContainedChild :: !child
33+
, inContainingChild :: !child
3234
}
3335
deriving (Eq, Ord, Show)
3436
deriving (Functor, Foldable, Traversable)

kore/src/Kore/Syntax/Inhabitant.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE Strict #-}
2+
13
{- |
24
Copyright : (c) Runtime Verification, 2019
35
License : NCSA

kore/src/Kore/Syntax/Mu.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE Strict #-}
2+
13
{- |
24
Copyright : (c) Runtime Verification, 2019
35
License : NCSA
@@ -24,7 +26,7 @@ The sort of the variable is the same as the sort of the result.
2426
-}
2527
data Mu variable child = Mu
2628
{ muVariable :: !(SetVariable variable)
27-
, muChild :: child
29+
, muChild :: !child
2830
}
2931
deriving (Eq, Ord, Show)
3032
deriving (Functor, Foldable, Traversable)

kore/src/Kore/Syntax/Next.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE Strict #-}
2+
13
{- |
24
Copyright : (c) Runtime Verification, 2019
35
License : NCSA
@@ -23,7 +25,7 @@ syntactic category from the Semantics of K, Section 9.1.4 (Patterns).
2325
-}
2426
data Next sort child = Next
2527
{ nextSort :: !sort
26-
, nextChild :: child
28+
, nextChild :: !child
2729
}
2830
deriving (Eq, Ord, Show)
2931
deriving (Functor, Foldable, Traversable)

kore/src/Kore/Syntax/Not.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE Strict #-}
2+
13
{- |
24
Copyright : (c) Runtime Verification, 2019
35
License : NCSA
@@ -25,7 +27,7 @@ Section 9.1.4 (Patterns).
2527
-}
2628
data Not sort child = Not
2729
{ notSort :: !sort
28-
, notChild :: child
30+
, notChild :: !child
2931
}
3032
deriving (Eq, Ord, Show)
3133
deriving (Functor, Foldable, Traversable)

kore/src/Kore/Syntax/Nu.hs

Lines changed: 3 additions & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE Strict #-}
2+
13
{- |
24
Copyright : (c) Runtime Verification, 2019
35
License : NCSA
@@ -24,7 +26,7 @@ The sort of the variable is the same as the sort of the result.
2426
-}
2527
data Nu variable child = Nu
2628
{ nuVariable :: !(SetVariable variable)
27-
, nuChild :: child
29+
, nuChild :: !child
2830
}
2931
deriving (Eq, Ord, Show)
3032
deriving (Functor, Foldable, Traversable)

kore/src/Kore/Syntax/Or.hs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE Strict #-}
2+
13
{- |
24
Copyright : (c) Runtime Verification, 2019
35
License : NCSA
@@ -27,8 +29,8 @@ Section 9.1.4 (Patterns).
2729
-}
2830
data Or sort child = Or
2931
{ orSort :: !sort
30-
, orFirst :: child
31-
, orSecond :: child
32+
, orFirst :: !child
33+
, orSecond :: !child
3234
}
3335
deriving (Eq, Ord, Show)
3436
deriving (Functor, Foldable, Traversable)

kore/src/Kore/Syntax/Rewrites.hs

Lines changed: 4 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE Strict #-}
2+
13
{- |
24
Copyright : (c) Runtime Verification, 2019
35
License : NCSA
@@ -23,8 +25,8 @@ syntactic category from the Semantics of K, Section 9.1.4 (Patterns).
2325
-}
2426
data Rewrites sort child = Rewrites
2527
{ rewritesSort :: !sort
26-
, rewritesFirst :: child
27-
, rewritesSecond :: child
28+
, rewritesFirst :: !child
29+
, rewritesSecond :: !child
2830
}
2931
deriving (Eq, Ord, Show)
3032
deriving (Functor, Foldable, Traversable)

kore/src/Kore/Syntax/StringLiteral.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE Strict #-}
2+
13
{- |
24
Copyright : (c) Runtime Verification, 2019
35
License : NCSA

kore/src/Kore/Syntax/Top.hs

Lines changed: 2 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -1,3 +1,5 @@
1+
{-# LANGUAGE Strict #-}
2+
13
{- |
24
Copyright : (c) Runtime Verification, 2019
35
License : NCSA

kore/src/Kore/Syntax/Variable.hs

Lines changed: 3 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -1,4 +1,5 @@
11
{-# LANGUAGE EmptyDataDeriving #-}
2+
{-# LANGUAGE Strict #-}
23

34
{- |
45
Copyright : (c) Runtime Verification, 2019
@@ -398,9 +399,9 @@ function in each field of @f@ to the value in the corresponding field of @a@.
398399
-}
399400
data AdjSomeVariableName a = AdjSomeVariableName
400401
{ -- | compare to: 'SomeVariableNameElement'
401-
adjSomeVariableNameElement :: ElementVariableName a
402+
adjSomeVariableNameElement :: !(ElementVariableName a)
402403
, -- | compare to: 'SomeVariableNameSet'
403-
adjSomeVariableNameSet :: SetVariableName a
404+
adjSomeVariableNameSet :: !(SetVariableName a)
404405
}
405406
deriving (Functor)
406407
deriving (GHC.Generic1)

0 commit comments

Comments
 (0)