Skip to content

Commit

Permalink
Remove the "condition" keyword
Browse files Browse the repository at this point in the history
There is no need to have two names for
the same operator so remove "condition"
and standardize on "?".
  • Loading branch information
pjonsson committed Jul 1, 2020
1 parent 2a3b2d3 commit 4de9368
Show file tree
Hide file tree
Showing 7 changed files with 11 additions and 16 deletions.
4 changes: 2 additions & 2 deletions examples/Examples/Simple/Basics.hs
Original file line number Diff line number Diff line change
Expand Up @@ -36,7 +36,7 @@ example8 b = not b
-- Examples on using conditionals:

example9 :: Data Int32 -> Data Int32
example9 a = condition (a<5) (3*(a+20)) (30*(a+20))
example9 a = a < 5 ? (3 * (a + 20)) $ 30 * (a + 20)

example10 :: Data Int32 -> Data Int32
example10 a = condition (a<5) (3*(a+a)) (30*(a+a))
example10 a = a < 5 ? (3 * (a + a)) $ 30 * (a + a)
5 changes: 2 additions & 3 deletions src/Feldspar/Algorithm/CRC.hs
Original file line number Diff line number Diff line change
Expand Up @@ -43,7 +43,7 @@ makeCrcTable polynomial = indexed1 256 $ \i -> forLoop 8 (i2n i .<<. (sz - 8)) s
where
sz = bitSize polynomial
step _ r = let r' = r .<<. 1
in condition (tstBit r (sz-1)) (r' `xor` polynomial) r'
in tstBit r (sz - 1) ? (r' `xor` polynomial) $ r'

-- | Calculate the normal form CRC using a table
crcNormal :: (Bits a)
Expand All @@ -67,9 +67,8 @@ crcNaive = crcNormal . makeCrcTable

-- | Reflect the bottom b bits of value t
reflect :: (Bits a) => Data a -> Data Length -> Data a
reflect t b = forLoop b t $ \i v -> let mask = bit ((b-1)-i) in condition (testBit t i) (v .|. mask) (v .&. complement mask)
reflect t b = forLoop b t $ \i v -> let mask = bit ((b-1)-i) in testBit t i ? (v .|. mask) $ v .&. complement mask

-- References
-- The functions in this module are inspired by the follow guide
-- http://www.ross.net/crc/download/crc_v3.txt

4 changes: 2 additions & 2 deletions src/Feldspar/Algorithm/FFT.hs
Original file line number Diff line number Diff line change
Expand Up @@ -56,7 +56,7 @@ fftCore n = composeOn stage (reverse (0...n))
where
stage k vec = indexed1 (length vec) ixf
where
ixf i = condition (testBit i k) (twid * (b - a)) (a+b)
ixf i = testBit i k ? (twid * (b - a)) $ a + b
where
a = vec !! i
b = vec !! (i `xor` k2)
Expand All @@ -68,7 +68,7 @@ ifftCore n = map (/ complex (i2f (2^(n+1))) 0) . composeOn stage (reverse (0...n
where
stage k vec = indexed1 (length vec) ixf
where
ixf i = condition (testBit i k) (twid * (b - a)) (a+b)
ixf i = testBit i k ? (twid * (b - a)) $ a + b
where
a = vec !! i
b = vec !! (i `xor` k2)
Expand Down
5 changes: 1 addition & 4 deletions src/Feldspar/Core/Language.hs
Original file line number Diff line number Diff line change
Expand Up @@ -287,16 +287,13 @@ iunit = 0 +. 1
-- Condition.hs
--------------------------------------------------

condition :: Syntax a => Data Bool -> a -> a -> a
condition = sugarSym3 Condition

-- | Condition operator. Use as follows:
-- > cond1 ? ex1 $
-- > cond2 ? ex2 $
-- > cond3 ? ex3 $
-- > exDefault
(?) :: Syntax a => Data Bool -> a -> a -> a
(?) = condition
(?) = sugarSym3 Condition

infixl 1 ?

Expand Down
2 changes: 1 addition & 1 deletion src/Feldspar/Stream.hs
Original file line number Diff line number Diff line change
Expand Up @@ -520,7 +520,7 @@ fir3 b (Stream ini) = Stream $ do
modifyRef y $ \x -> x + r * b!(Z:.n)
setRef nref (n+1)
modifyRef k (\x -> x-1)
setRef top $ condition (t+1> i2n (length b)) 0 (t+1)
setRef top (t + 1 > i2n (length b) ? 0 $ t + 1)
getRef y

-- | An iir filter on streams
Expand Down
3 changes: 1 addition & 2 deletions tests/DecorationTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -23,7 +23,7 @@ import Feldspar.Core.NestedTuples


topLevelConsts :: Data Index -> Data Index -> Data Index
topLevelConsts a b = condition (b<5) (d ! (a+5)) (c ! (a+5))
topLevelConsts a b = b < 5 ? (d ! (a + 5)) $ c ! (a + 5)
where
c = value [1,2,3,4,5] :: Data [Index]
d = value [2,3,4,5,6] :: Data [Index]
Expand Down Expand Up @@ -78,4 +78,3 @@ tests = testGroup "DecorationTests"
]

main = defaultMain $ testGroup "Tests" [tests]

4 changes: 2 additions & 2 deletions tests/RegressionTests.hs
Original file line number Diff line number Diff line change
Expand Up @@ -40,13 +40,13 @@ vgReadFiles :: String -> IO LB.ByteString
vgReadFiles base = liftM LB.concat $ mapM (LB.readFile . (base<>)) [".h",".c"]

example9 :: Data Int32 -> Data Int32
example9 a = condition (a<5) (3*(a+20)) (30*(a+20))
example9 a = a < 5 ? (3 * (a + 20)) $ 30 * (a + 20)

-- Compile and load example9 as c_example9 (using plugins)
loadFun ['example9]

topLevelConsts :: Data Index -> Data Index -> Data Index
topLevelConsts a b = condition (a<5) (d ! (b+5)) (c ! (b+5))
topLevelConsts a b = a < 5 ? (d ! (b + 5)) $ c ! (b + 5)
where
c = value [1,2,3,4,5] :: Data [Index]
d = value [2,3,4,5,6] :: Data [Index]
Expand Down

0 comments on commit 4de9368

Please sign in to comment.