Skip to content

Commit

Permalink
make ormolu happy
Browse files Browse the repository at this point in the history
  • Loading branch information
lukaszcz committed Aug 22, 2022
1 parent 7e10c7c commit e78be96
Show file tree
Hide file tree
Showing 8 changed files with 50 additions and 55 deletions.
7 changes: 3 additions & 4 deletions src/Juvix/Compiler/Core/Pretty/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -69,10 +69,9 @@ instance PrettyCode Node where
Just ni -> do
showDeBruijn <- asks (^. optShowDeBruijnIndices)
n <- ppCode (ni ^. NameInfo.infoName)
if showDeBruijn then
return $ n <> kwDeBruijnVar <> pretty varIndex
else
return n
if showDeBruijn
then return $ n <> kwDeBruijnVar <> pretty varIndex
else return n
Nothing -> return $ kwDeBruijnVar <> pretty varIndex
Ident {..} ->
case Info.lookup kNameInfo identInfo of
Expand Down
4 changes: 2 additions & 2 deletions src/Juvix/Prelude/Base.hs
Original file line number Diff line number Diff line change
Expand Up @@ -223,8 +223,8 @@ tableNestedInsert k1 k2 = tableInsert (HashMap.singleton k2) (HashMap.insert k2)
--------------------------------------------------------------------------------

revAppend :: [a] -> [a] -> [a]
revAppend [] !ys = ys
revAppend (x : xs) !ys = revAppend xs (x : ys)
revAppend [] ys = ys
revAppend (x : xs) ys = revAppend xs (x : ys)

--------------------------------------------------------------------------------
-- NonEmpty
Expand Down
4 changes: 2 additions & 2 deletions test/Core.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,8 @@
module Core where

import Core.Positive qualified as P
import Core.Negative qualified as N
import Base
import Core.Negative qualified as N
import Core.Positive qualified as P

allTests :: TestTree
allTests = testGroup "JuvixCore tests" [P.allTests, N.allTests]
3 changes: 2 additions & 1 deletion test/Core/Negative.hs
Original file line number Diff line number Diff line change
Expand Up @@ -18,7 +18,8 @@ testDescr NegTest {..} =
in TestDescr
{ _testName = _name,
_testRoot = tRoot,
_testAssertion = Steps $ coreEvalErrorAssertion _file }
_testAssertion = Steps $ coreEvalErrorAssertion _file
}

allTests :: TestTree
allTests =
Expand Down
13 changes: 7 additions & 6 deletions test/Core/Positive.hs
Original file line number Diff line number Diff line change
Expand Up @@ -19,7 +19,8 @@ testDescr PosTest {..} =
in TestDescr
{ _testName = _name,
_testRoot = tRoot,
_testAssertion = Steps $ coreEvalAssertion _file _expectedFile }
_testAssertion = Steps $ coreEvalAssertion _file _expectedFile
}

allTests :: TestTree
allTests =
Expand Down Expand Up @@ -194,11 +195,11 @@ tests =
"."
"test033.jvc"
"out/test033.out",
{- PosTest
"Evaluation order"
"."
"test034.jvc"
"out/test034.out", -}
{- PosTest
"Evaluation order"
"."
"test034.jvc"
"out/test034.out", -}
PosTest
"Merge sort"
"."
Expand Down
28 changes: 14 additions & 14 deletions tests/Core/positive/reference/test026.hs
Original file line number Diff line number Diff line change
@@ -1,4 +1,3 @@

data Tree = Leaf | Node Tree Tree

gen :: Int -> Tree
Expand All @@ -7,26 +6,27 @@ gen n = if n <= 0 then Leaf else Node (gen (n - 2)) (gen (n - 1))
f :: Tree -> Integer
f Leaf = 1
f (Node l r) =
let l' = g l in
let r' = g r in
let a = case l' of
Leaf -> -3
Node l r -> f l + f r
in
let b = case r' of
Node l r -> f l + f r
_ -> 2
in
a * b
let l' = g l
in let r' = g r
in let a = case l' of
Leaf -> -3
Node l r -> f l + f r
in let b = case r' of
Node l r -> f l + f r
_ -> 2
in a * b

isNode :: Tree -> Bool
isNode (Node _ _ ) = True
isNode (Node _ _) = True
isNode Leaf = False

isLeaf :: Tree -> Bool
isLeaf Leaf = True
isLeaf _ = False

g :: Tree -> Tree
g t = if isLeaf t then t else case t of
g t =
if isLeaf t
then t
else case t of
Node l r -> if isNode l then r else Node r l
3 changes: 1 addition & 2 deletions tests/Core/positive/reference/test030.hs
Original file line number Diff line number Diff line change
@@ -1,8 +1,7 @@

import Data.List

eratostenes :: [Integer] -> [Integer]
eratostenes (h : t) = h : eratostenes (filter (\x -> x `mod` h /= 0) t)

primes :: [Integer]
primes = eratostenes [2..]
primes = eratostenes [2 ..]
43 changes: 19 additions & 24 deletions tests/Core/positive/reference/test036.hs
Original file line number Diff line number Diff line change
@@ -1,12 +1,10 @@

power :: Integer -> Int -> Integer
power x y = power' x y 1
where
power' x y acc =
if y == 0 then
acc
else
power' x (y - 1) (x * acc)
if y == 0
then acc
else power' x (y - 1) (x * acc)

num1 :: Integer
num1 = 1267650600228229401496703205376
Expand All @@ -18,35 +16,32 @@ msqrt :: Integer -> Integer
msqrt x = sqrt' x (x + 1) 0
where
sqrt' x top bot =
if top - bot <= 1 then
bot
else
let y = (top + bot) `div` 2
in
if y * y > x then
sqrt' x y bot
else
sqrt' x top y
if top - bot <= 1
then bot
else
let y = (top + bot) `div` 2
in if y * y > x
then sqrt' x y bot
else sqrt' x top y

dlog :: Integer -> Integer -> Integer
dlog x y = log' x y 0
where
log' x y acc =
if y == 1 then
acc
else
log' x (y `div` x) (acc + 1)
if y == 1
then acc
else log' x (y `div` x) (acc + 1)

fast_power :: Integer -> Int -> Integer
fast_power x y = fast_power' x y 1
where
fast_power' x y acc =
if y == 0 then
acc
else if y `mod` 2 == 1 then
fast_power' (x * x) (y `div` 2) (x * acc)
else
fast_power' (x * x) (y `div` 2) acc
if y == 0
then acc
else
if y `mod` 2 == 1
then fast_power' (x * x) (y `div` 2) (x * acc)
else fast_power' (x * x) (y `div` 2) acc

main :: IO ()
main = do
Expand Down

0 comments on commit e78be96

Please sign in to comment.