Skip to content

Commit d962c5a

Browse files
committed
Fix typos in .hs files, refs #560
1 parent ce25043 commit d962c5a

File tree

18 files changed

+27
-27
lines changed

18 files changed

+27
-27
lines changed

copilot-c99/src/Copilot/Compile/C99/CodeGen.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -267,7 +267,7 @@ mkStep cSettings streams triggers exts =
267267
--
268268
-- We create temporary variables because:
269269
--
270-
-- 1. We want to pass structs by reference intead of by value. To this end,
270+
-- 1. We want to pass structs by reference instead of by value. To this end,
271271
-- we use C's & operator to obtain a reference to a temporary variable
272272
-- of a struct type and pass that to the handler function.
273273
--

copilot-c99/tests/Test/Copilot/Compile/C99.hs

Lines changed: 3 additions & 3 deletions
Original file line numberDiff line numberDiff line change
@@ -240,9 +240,9 @@ arbitraryOpBoolBits =
240240
]
241241

242242
-- | Generator of functions that take Nums and produce booleans.
243-
arbitaryOpBoolOrdEqNum :: (Typed a, Eq a, Ord a, Num a)
243+
arbitraryOpBoolOrdEqNum :: (Typed a, Eq a, Ord a, Num a)
244244
=> Gen (Fun a Bool, [a] -> [Bool])
245-
arbitaryOpBoolOrdEqNum =
245+
arbitraryOpBoolOrdEqNum =
246246
frequency
247247
[ (1, funCompose2 <$> arbitraryOp2Eq <*> arbitraryOpNum <*> arbitraryOpNum)
248248
, (1, funCompose2 <$> arbitraryOp2Ord <*> arbitraryOpNum <*> arbitraryOpNum)
@@ -379,7 +379,7 @@ arbitraryOpIntegralBool = frequency
379379

380380
-- we need to use +1 because certain operations overflow the number
381381
, (2, mkTestCase1
382-
arbitaryOpBoolOrdEqNum
382+
arbitraryOpBoolOrdEqNum
383383
(chooseBoundedIntegral (minBound + 1, maxBound)))
384384
]
385385

copilot-interpreter/src/Copilot/Interpret/Eval.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -106,7 +106,7 @@ data ExecTrace = ExecTrace
106106

107107
-- We could write this in a beautiful lazy style like above, but that creates a
108108
-- space leak in the interpreter that is hard to fix while maintaining laziness.
109-
-- We take a more brute-force appraoch below.
109+
-- We take a more brute-force approach below.
110110

111111
-- | Evaluate a specification for a number of steps.
112112
eval :: ShowType -- ^ Show booleans as @0@\/@1@ (C) or @True@\/@False@

copilot-interpreter/src/Copilot/Interpret/Render.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -16,7 +16,7 @@ import Text.PrettyPrint
1616

1717
import Prelude hiding ((<>))
1818

19-
-- | Render an execution trace as a table, formatted to faciliate readability.
19+
-- | Render an execution trace as a table, formatted to facilitate readability.
2020
renderAsTable :: ExecTrace -> String
2121
renderAsTable
2222
ExecTrace
@@ -112,7 +112,7 @@ pad :: Int -> Int -> a -> [a] -> [a]
112112
pad lx max b ls = ls ++ replicate (max - lx) b
113113

114114
-- | Pad a list of strings on the right with spaces.
115-
pad' :: Int -- ^ Mininum number of spaces to add
115+
pad' :: Int -- ^ Minimum number of spaces to add
116116
-> Int -- ^ Maximum number of spaces to add
117117
-> [[Doc]] -- ^ List of documents to pad
118118
-> [[Doc]]

copilot-language/src/Copilot/Language/Analyze.hs

Lines changed: 2 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -60,13 +60,13 @@ instance Show AnalyzeException where
6060
show (DifferentTypes name) = badUsage $
6161
"The external symbol \'" ++ name ++ "\' has been declared to have two different types!"
6262
show (Redeclared name) = badUsage $
63-
"The external symbol \'" ++ name ++ "\' has been redeclared to be a different symbol (e.g., a variable and an array, or a variable and a funciton symbol, etc.)."
63+
"The external symbol \'" ++ name ++ "\' has been redeclared to be a different symbol (e.g., a variable and an array, or a variable and a function symbol, etc.)."
6464
show (BadNumberOfArgs name) = badUsage $
6565
"The function symbol \'" ++ name ++ "\' has been redeclared to have different number of arguments."
6666
show (BadFunctionArgType name) = badUsage $
6767
"The function symbol \'" ++ name ++ "\' has been redeclared to an argument with different types."
6868

69-
-- | 'Exception' instance so we can throw and catch 'AnalyzeExcetion's.
69+
-- | 'Exception' instance so we can throw and catch 'AnalyzeException's.
7070
instance Exception AnalyzeException
7171

7272
-- | Max level of recursion supported. Any level above this constant

copilot-language/src/Copilot/Language/Operators/Integral.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -46,4 +46,4 @@ x `mod` y = Op2 (Core.Mod typeOf) x y
4646
(Const x) ^ (Const y) = Const (x P.^ y)
4747
(Const 2) ^ y = (Const 1) .<<. y
4848
x ^ (Const y) = foldl' ((P.*)) (Const 1) (replicate (P.fromIntegral y) x)
49-
_ ^ _ = Err.badUsage "in ^: in x ^ y, either x must be the constant 2, or y must be a constant. (Do not confuse ^ with bitwise XOR (.^.) or with ** for exponentation of floats/doubles.)"
49+
_ ^ _ = Err.badUsage "in ^: in x ^ y, either x must be the constant 2, or y must be a constant. (Do not confuse ^ with bitwise XOR (.^.) or with ** for exponentiation of floats/doubles.)"

copilot-libraries/src/Copilot/Library/Statistics.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -32,7 +32,7 @@ min n s = nfoldl1 n smallest s
3232
smallest = \ x y -> mux ( x <= y ) x y
3333

3434
-- | Mean value. @n@ must not overflow
35-
-- for word size @a@ for streams over which computation is peformed.
35+
-- for word size @a@ for streams over which computation is performed.
3636
mean :: ( Typed a, Eq a, Fractional a ) => Int -> Stream a -> Stream a
3737
mean n s = ( sum n s ) / ( fromIntegral n )
3838

copilot-theorem/src/Copilot/Theorem/Kind2/PrettyPrint.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -9,7 +9,7 @@ import Copilot.Theorem.Kind2.AST
99

1010
import Data.List (intercalate)
1111

12-
-- | A tree of expressions, in which the leafs are strings.
12+
-- | A tree of expressions, in which the leaves are strings.
1313
type SSExpr = SExpr String
1414

1515
-- | Reserved keyword prime.

copilot-theorem/src/Copilot/Theorem/TransSys/Invariants.hs

Lines changed: 1 addition & 1 deletion
Original file line numberDiff line numberDiff line change
@@ -8,7 +8,7 @@ module Copilot.Theorem.TransSys.Invariants
88
, prop
99
) where
1010

11-
-- | Type class for types with additional invariants or contraints.
11+
-- | Type class for types with additional invariants or constraints.
1212
class HasInvariants a where
1313

1414
invariants :: a -> [(String, Bool)]

copilot-theorem/src/Copilot/Theorem/TransSys/Spec.hs

Lines changed: 4 additions & 4 deletions
Original file line numberDiff line numberDiff line change
@@ -74,11 +74,11 @@ data Node = Node
7474
-- its local name.
7575
, nodeConstrs :: [Expr Bool] }
7676

77-
-- | Identifer of a variable in the local (within one node) namespace.
77+
-- | Identifier of a variable in the local (within one node) namespace.
7878
data Var = Var {varName :: String}
7979
deriving (Eq, Show, Ord)
8080

81-
-- | Identifer of a variable in the global namespace by specifying both a node
81+
-- | Identifier of a variable in the global namespace by specifying both a node
8282
-- name and a variable.
8383
data ExtVar = ExtVar {extVarNode :: NodeId, extVarLocalPart :: Var }
8484
deriving (Eq, Ord)
@@ -115,7 +115,7 @@ foldExpr f expr = f expr <> fargs
115115
foldUExpr :: (Monoid m) => (forall t . Expr t -> m) -> U Expr -> m
116116
foldUExpr f (U e) = foldExpr f e
117117

118-
-- | Apply an arbitrary transformation to the leafs of an expression.
118+
-- | Apply an arbitrary transformation to the leaves of an expression.
119119
transformExpr :: (forall a . Expr a -> Expr a) -> Expr t -> Expr t
120120
transformExpr f = tre
121121
where
@@ -126,7 +126,7 @@ transformExpr f = tre
126126
tre e = f e
127127

128128
-- | The set of variables related to a node (union of the local variables and
129-
-- the imported variables after deferencing them).
129+
-- the imported variables after dereferencing them).
130130
nodeVarsSet :: Node -> Set Var
131131
nodeVarsSet = liftA2 Set.union
132132
nodeLocalVarsSet

0 commit comments

Comments
 (0)