Skip to content

Instantly share code, notes, and snippets.

@beckyconning
Created April 2, 2018 17:59
Show Gist options
  • Save beckyconning/18ab574cbed65fd1e71918bb04a636ae to your computer and use it in GitHub Desktop.
Save beckyconning/18ab574cbed65fd1e71918bb04a636ae to your computer and use it in GitHub Desktop.
module Main where
import Prelude
import Control.Monad.Eff (Eff)
import Control.Monad.Eff.Console (CONSOLE, log)
import Control.Monad.Eff.Random (RANDOM, random)
import Control.Monad.Loops (iterateUntilM)
import Data.Array as Array
import Data.Either (Either)
import Data.Int as Int
import Data.List (List(..), length)
import Math (pow)
import Data.NonEmpty (NonEmpty(NonEmpty), (:|))
import Data.Maybe (Maybe, maybe)
main :: forall e. Eff (console :: CONSOLE | e) Unit
main = do
log $ show $ nextQuota 1000 900 25
nextQuota :: Int -> Int -> Int -> Int
nextQuota current used markedAsSpam =
Int.floor
(max
0.0
(unpunished
- (unpunished * punish (Int.toNumber markedAsSpam / currentNumber))))
where
currentNumber = Int.toNumber current
unpunished = currentNumber + (currentNumber * maxReward current)
punish :: Number -> Number
punish markedAsSpam =
3.631953 + (-652.999 - 3.631953)
/ (1.0 + (markedAsSpam / 2.927795e-20) `pow` 0.1265019)
maxReward :: Int -> Number
maxReward currentQuota =
-0.04426271 + (1.002206 + 0.04426271)
/ (1.0 + (Int.toNumber currentQuota / 1189568.0) `pow` 0.4632819)
type MarkedAsSpam =
{ sentId :: String
, timestamp :: String
}
type Sent =
{ from :: String
, to :: String
, subject :: String
, timestamp :: String
, id :: String
}
type Customer =
{ name :: String
, addresses :: Array String
, sendProbability :: Number
, dailyQuota :: Int
, markedAsSpamProbability :: Number
, timestamp :: String
, id :: String
}
type State =
{ result :: List (Either Customer (Either Sent MarkedAsSpam))
, fromAddresses :: NonEmpty Array String
, toAddresses :: NonEmpty Array String
, subjects :: NonEmpty Array String
, companyNames :: NonEmpty Array String
}
initialState :: State
initialState =
{ result: Nil
, fromAddresses: "[email protected]" :| ["[email protected]", "[email protected]", "[email protected]"]
, toAddresses: "[email protected]" :| ["[email protected]", "[email protected]", "[email protected]"]
, subjects: "Welcome!" :| ["Password reset", "Latest deals", "Hi!", "We miss you!"]
, companyNames: "awnhe" :| ["kaead", "gobhe", "hiemps", "amuin", "usirk", "atduh"]
}
crank :: forall a. NonEmpty Array a -> NonEmpty Array a
crank (NonEmpty x xs) =
maybe (NonEmpty x []) (flip NonEmpty (Array.snoc xs x)) (Array.head xs)
runProbability :: Number -> Eff (random :: RANDOM) Boolean
runProbability =
(<#>) random <<< (>=)
-- iterateUntilM :: forall a m. MonadRec m => (a -> Boolean) -> (a -> m a) -> a -> m a
--x :: _
--x =
-- iterateUntilM ((<=) 1000 <<< length) step Nil
step :: State -> Eff (random :: RANDOM) State
step state =
pure state
--runProbability 0.1 >>= if _ then pure state else
Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment