Skip to content

Commit cd095db

Browse files
committed
Apply partial applicative operators for Eq and Ord-like functions.
1 parent 24d7979 commit cd095db

File tree

7 files changed

+9
-9
lines changed

7 files changed

+9
-9
lines changed

clash-prelude/tests/Clash/Tests/BlockRam.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,7 @@ readRam
1414
:: (HiddenClockResetEnable dom)
1515
=> Signal dom (Unsigned 4)
1616
-> Signal dom (Unsigned 8)
17-
readRam addr = mux (register False $ addr .<. 8) ram (pure 0xff)
17+
readRam addr = mux (register False $ addr .< 8) ram (pure 0xff)
1818
where
1919
ram = blockRam1 NoClearOnReset (SNat @8) 0 addr (pure Nothing)
2020

clash-prelude/tests/Clash/Tests/Ram.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -51,7 +51,7 @@ ram rd we wr din =
5151

5252
maskOobRead :: Ram
5353
maskOobRead rd we wr din =
54-
maybeIsX <$> mux (rd .<. 2) ram0 (pure 4)
54+
maybeIsX <$> mux (rd .< 2) ram0 (pure 4)
5555
where
5656
ram0 = asyncRam# clockGen clockGen enableGen d2 rd we wr din
5757

tests/shouldfail/Verification/NonTemporal.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -25,7 +25,7 @@ assertCvResult
2525
assertCvResult clk rst gen max results = done
2626
where
2727
counter = register clk rst gen (minBound :: n) (succ <$> counter)
28-
done = hideAssertion results (counter .==. pure maxBound)
28+
done = hideAssertion results (counter .== maxBound)
2929
{-# INLINE assertCvResult #-}
3030

3131
binaryTest

tests/shouldwork/Basic/AES.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -89,7 +89,7 @@ aes
8989
-> Signal dom (BitVector 128)
9090
-> Signal dom (BitVector 128)
9191
-> Signal dom (Unsigned 4, Vec 4 (BitVector 32), BitVector 128, Bool)
92-
aes start key block = bundle (cnt, roundKey, pack <$> roundState, cnt .==. 11)
92+
aes start key block = bundle (cnt, roundKey, pack <$> roundState, cnt .== 11)
9393
where
9494

9595
roundKey :: Signal dom (Vec 4 (BitVector 32))

tests/shouldwork/Cores/Xilinx/DcFifo/Lfsr.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -156,10 +156,10 @@ fifoVerifier ::
156156
fifoVerifier clk rst ena actual = done0
157157
where
158158
expected = regEn clk rst ena 0 (isJust <$> actual) $ expected + 1
159-
samplesDone = expected .>. 100
159+
samplesDone = expected .> 100
160160
stuckCnt :: Signal dom (Index 25000)
161161
stuckCnt = regEn clk rst ena 0 (not <$> stuck) $ stuckCnt + 1
162-
stuck = stuckCnt .==. pure maxBound
162+
stuck = stuckCnt .== maxBound
163163
-- Delay one cycle so assertion definitely triggers before stopping simulation
164164
done = register clk rst ena False $ samplesDone .||. stuck
165165
expected0 = liftA2 (<$) expected actual

tests/shouldwork/Issues/T1187/Utils.hs

+1-1
Original file line numberDiff line numberDiff line change
@@ -26,7 +26,7 @@ debounce _ initial this = regEn initial stable this
2626
where
2727
counter = register (0 :: Index (ClockDivider dom ps)) counter'
2828
counter' = mux (unchanged initial this) counter 0
29-
stable = counter' .==. pure maxBound
29+
stable = counter' .== maxBound
3030

3131
roundRobin
3232
:: forall n dom. (KnownNat n, HiddenClockResetEnable dom)

tests/shouldwork/Xilinx/ClockWizard.hs

+2-2
Original file line numberDiff line numberDiff line change
@@ -40,8 +40,8 @@ testBench ::
4040
testBench = done
4141
where
4242
(o1, o2) = unbundle $ topEntity clkSE clkDiff rst
43-
done1 = o1 .==. pure maxBound
44-
done2 = o2 .==. pure maxBound
43+
done1 = o1 .== maxBound
44+
done2 = o2 .== maxBound
4545
done = unsafeSynchronizer clockGen clkSE $ fmap endVhdlSim $
4646
strictAnd <$> done1 <*> done2
4747
strictAnd !a !b = a && b

0 commit comments

Comments
 (0)