Skip to content

Commit d216c3b

Browse files
authored
Merge pull request #7 from safareli/frequency
fix frequency
2 parents c17dc11 + 367366d commit d216c3b

File tree

6 files changed

+107
-7
lines changed

6 files changed

+107
-7
lines changed

.travis.yml

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -14,6 +14,7 @@ install:
1414
- bower install
1515
script:
1616
- npm run -s build
17+
- npm run -s test
1718
after_success:
1819
- >-
1920
test $TRAVIS_TAG &&

bower.json

Lines changed: 7 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -21,5 +21,12 @@
2121
"purescript-tuples": "^4.0.0",
2222
"purescript-unfoldable": "^3.0.0",
2323
"purescript-integers": "^3.0.0"
24+
},
25+
"devDependencies": {
26+
"purescript-console": "^3.0.0",
27+
"purescript-assert": "^3.0.0",
28+
"purescript-arrays": "^4.2.1",
29+
"purescript-transformers": "^3.4.0",
30+
"purescript-math": "^2.1.0"
2431
}
2532
}

package.json

Lines changed: 1 addition & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -2,6 +2,7 @@
22
"private": true,
33
"scripts": {
44
"clean": "rimraf output && rimraf .pulp-cache",
5+
"test": "pulp test",
56
"build": "pulp build -- --censor-lib --strict"
67
},
78
"devDependencies": {

src/Control/Monad/Gen.purs

Lines changed: 17 additions & 7 deletions
Original file line numberDiff line numberDiff line change
@@ -14,7 +14,6 @@ import Control.Monad.Gen.Class (class MonadGen, Size, chooseBool, chooseFloat, c
1414
import Control.Monad.Rec.Class (class MonadRec, Step(..), tailRecM)
1515

1616
import Data.Foldable (class Foldable, length, foldl, foldMap)
17-
import Data.Int as Int
1817
import Data.Maybe (Maybe(..), fromMaybe)
1918
import Data.Monoid.Additive (Additive(..))
2019
import Data.Newtype (alaF)
@@ -46,15 +45,26 @@ frequency
4645
=> Foldable f
4746
=> NonEmpty f (Tuple Number (m a))
4847
-> m a
49-
frequency (x :| xs) =
48+
frequency (x :| xs) =
5049
let
5150
first = fst x
5251
total = first + alaF Additive foldMap fst xs
53-
in do
54-
pos <- chooseFloat 0.0 total
55-
let n = Int.round (pos / total * length xs)
56-
snd $ if n == 0 then x else fromIndex (n - 1) x xs
57-
52+
in
53+
chooseFloat 0.0 total >>= pick
54+
where
55+
pick pos =
56+
let
57+
initial = go (Tuple 0.0 $ snd x) x
58+
in
59+
snd $ foldl go initial xs
60+
where
61+
go (Tuple weight val) (Tuple currWeight currVal) =
62+
let
63+
nextWeight = weight + currWeight
64+
in
65+
if weight <= pos && pos <= nextWeight
66+
then Tuple nextWeight currVal
67+
else Tuple nextWeight val
5868
-- | Creates a generator that outputs a value chosen from a selection with
5969
-- | uniform probability.
6070
elements :: forall m f a. MonadGen m => Foldable f => NonEmpty f a -> m a

test/Test/Frequency.purs

Lines changed: 65 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,65 @@
1+
module Test.Frequency where
2+
3+
import Prelude
4+
5+
import Test.Assert (ASSERT, assert)
6+
import Partial.Unsafe (unsafeCrashWith)
7+
import Control.Monad.Eff (Eff)
8+
import Control.Monad.Gen (class MonadGen, frequency)
9+
import Data.NonEmpty ((:|), NonEmpty(..))
10+
import Data.Traversable (sequence)
11+
import Data.Array (replicate, group', length)
12+
import Data.Tuple (Tuple(..))
13+
import Data.Newtype (unwrap)
14+
import Math (remainder)
15+
import Control.Monad.State (State, class MonadState, get, put, evalStateT)
16+
17+
18+
newtype TestGenFrequency a = TestGenFrequency (State Number a)
19+
derive newtype instance testGenFunctor :: Functor TestGenFrequency
20+
derive newtype instance testGenApply :: Apply TestGenFrequency
21+
derive newtype instance testGenBind :: Bind TestGenFrequency
22+
derive newtype instance testGenApplicative :: Applicative TestGenFrequency
23+
derive newtype instance testGenMonad :: Monad TestGenFrequency
24+
derive newtype instance testGenMonadState :: MonadState Number TestGenFrequency
25+
26+
instance testGenMonadGen :: MonadGen TestGenFrequency where
27+
sized _ = unsafeCrashWith "sized should not be called"
28+
resize _ _ = unsafeCrashWith "resize should not be called"
29+
chooseBool = pure unit >>= \_ -> unsafeCrashWith "chooseBool should not be called"
30+
chooseFloat s e = do
31+
c <- get
32+
put (c + 1.0)
33+
pure ((s + c) `remainder` e)
34+
chooseInt _ _ = unsafeCrashWith "chooseFloat should not be called"
35+
36+
runTestGenFrequency :: TestGenFrequency ~> State Number
37+
runTestGenFrequency (TestGenFrequency x) = x
38+
39+
check :: forall r. Eff (assert :: ASSERT | r) Unit
40+
check =
41+
let
42+
abcGen :: TestGenFrequency String
43+
abcGen =
44+
frequency $
45+
( Tuple 10.0 $ pure "A" ) :|
46+
[ Tuple 20.0 $ pure "B"
47+
, Tuple 0.0 $ pure "Z"
48+
, Tuple 30.0 $ pure "C"
49+
, Tuple 40.0 $ pure "D"
50+
, Tuple 50.0 $ pure "E"
51+
, Tuple 50.0 $ pure "F"
52+
]
53+
abcArrGen = sequence $ replicate 200 abcGen
54+
abcArr = runTestGenFrequency abcArrGen `evalStateT` 0.0 # unwrap
55+
actual = group' abcArr <#> \(NonEmpty x xs) -> Tuple (length xs + 1) x
56+
expected =
57+
[ (Tuple 10 "A")
58+
, (Tuple 20 "B")
59+
, (Tuple 30 "C")
60+
, (Tuple 40 "D")
61+
, (Tuple 50 "E")
62+
, (Tuple 50 "F")
63+
]
64+
in
65+
assert (expected == actual)

test/Test/Main.purs

Lines changed: 16 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,16 @@
1+
module Test.Main where
2+
3+
import Prelude
4+
5+
import Test.Frequency as Frequency
6+
import Test.Assert (ASSERT)
7+
import Control.Monad.Eff (Eff)
8+
import Control.Monad.Eff.Console (CONSOLE, log)
9+
10+
type Tests = Eff (console :: CONSOLE, assert :: ASSERT) Unit
11+
12+
main :: Tests
13+
main = do
14+
log "check frequency"
15+
Frequency.check
16+

0 commit comments

Comments
 (0)