Skip to content

Commit 65e54c4

Browse files
committed
Updates for PureScript 0.9
1 parent 9c9cd42 commit 65e54c4

File tree

3 files changed

+25
-18
lines changed

3 files changed

+25
-18
lines changed

bower.json

Lines changed: 5 additions & 5 deletions
Original file line numberDiff line numberDiff line change
@@ -20,12 +20,12 @@
2020
"package.json"
2121
],
2222
"dependencies": {
23-
"purescript-maybe": "^0.3.2"
23+
"purescript-maybe": "^1.0.0"
2424
},
2525
"devDependencies": {
26-
"purescript-integers": "^0.2.1",
27-
"purescript-console": "^0.1.0",
28-
"purescript-assert": "^0.1.1",
29-
"purescript-quickcheck": "^0.12.0"
26+
"purescript-integers": "^1.0.0",
27+
"purescript-console": "^1.0.0",
28+
"purescript-assert": "^1.0.0",
29+
"purescript-quickcheck": "^1.0.0"
3030
}
3131
}

src/Data/BigInt.purs

Lines changed: 5 additions & 2 deletions
Original file line numberDiff line numberDiff line change
@@ -90,7 +90,7 @@ instance ordBigInt :: Ord BigInt where
9090
foreign import toString :: BigInt -> String
9191

9292
instance showBigInt :: Show BigInt where
93-
show x = "fromString \"" ++ toString x ++ "\""
93+
show x = "fromString \"" <> toString x <> "\""
9494

9595
foreign import biAdd :: BigInt -> BigInt -> BigInt
9696
foreign import biMul :: BigInt -> BigInt -> BigInt
@@ -109,6 +109,9 @@ instance ringBigInt :: Ring BigInt where
109109
foreign import biDiv :: BigInt -> BigInt -> BigInt
110110
foreign import biMod :: BigInt -> BigInt -> BigInt
111111

112-
instance moduloSemiringBigInt :: ModuloSemiring BigInt where
112+
instance commutativeRingBigInt :: CommutativeRing BigInt
113+
114+
instance euclideanRingBigInt :: EuclideanRing BigInt where
113115
div = biDiv
114116
mod = biMod
117+
degree = degree <<< toNumber

test/Main.purs

Lines changed: 15 additions & 11 deletions
Original file line numberDiff line numberDiff line change
@@ -1,17 +1,20 @@
11
module Test.Main where
22

33
import Prelude
4-
import Control.Monad.Eff.Console (log)
4+
import Control.Monad.Eff (Eff)
5+
import Control.Monad.Eff.Console (CONSOLE, log)
56
import Data.Array (filter, range)
6-
import Data.BigInt
7-
import Data.Foldable (mconcat)
8-
import Data.Maybe (Maybe(..))
9-
import Data.Maybe.Unsafe (fromJust)
10-
import Test.Assert (assert)
7+
import Data.BigInt (BigInt, abs, fromInt, prime, pow, odd, even, fromString,
8+
toNumber, fromBase, toString)
9+
import Data.Foldable (fold)
10+
import Data.Maybe (Maybe(..), fromMaybe)
11+
import Test.Assert (ASSERT, assert)
12+
import Control.Monad.Eff.Random (RANDOM())
13+
import Control.Monad.Eff.Exception (EXCEPTION())
1114
import Test.QuickCheck (QC(), quickCheck)
12-
import Test.QuickCheck.Arbitrary (Arbitrary)
15+
import Test.QuickCheck.Arbitrary (class Arbitrary)
1316
import Test.QuickCheck.Gen (Gen(), chooseInt, arrayOf, elements)
14-
import qualified Data.Int as Int
17+
import Data.Int as Int
1518

1619
-- | Newtype with an Arbitrary instance that generates only small integers
1720
newtype SmallInt = SmallInt Int
@@ -27,13 +30,13 @@ newtype TestBigInt = TestBigInt BigInt
2730

2831
instance arbitraryBigInt :: Arbitrary TestBigInt where
2932
arbitrary = do
30-
n <- (fromJust <<< fromString) <$> digitString
33+
n <- (fromMaybe zero <<< fromString) <$> digitString
3134
op <- elements id [negate]
32-
return (TestBigInt (op n))
35+
pure (TestBigInt (op n))
3336
where digits :: Gen Int
3437
digits = chooseInt 0 9
3538
digitString :: Gen String
36-
digitString = (mconcat <<< map show) <$> arrayOf digits
39+
digitString = (fold <<< map show) <$> arrayOf digits
3740

3841
-- | Convert SmallInt to BigInt
3942
fromSmallInt :: SmallInt -> BigInt
@@ -45,6 +48,7 @@ testBinary :: forall eff. (BigInt -> BigInt -> BigInt)
4548
-> QC eff Unit
4649
testBinary f g = quickCheck (\x y -> (fromInt x) `f` (fromInt y) == fromInt (x `g` y))
4750

51+
main :: forall eff. Eff (console :: CONSOLE, assert :: ASSERT, random :: RANDOM, err :: EXCEPTION | eff) Unit
4852
main = do
4953
log "Simple arithmetic operations and conversions from Int"
5054
let two = one + one

0 commit comments

Comments
 (0)