module Data.HashFlare
(
MEFTable, makeMEFTable
, PayoutTable, makePayoutTable
, MiningContract, makeMiningContract, makeMiningContractSimple
, UserAccount, makeUserAccount
, contractHashrate
, contractCost
, contractExpiration
, contractMEF
, contractPayout
, accountBalance
, accountContracts
, userAccountMEF
, userAccountPayout
, infoUserAccount
, defaultMEFTable
)
where
import Data.Money
import Data.Hashrate
import qualified Data.Map as M
import Data.Typeable
data MiningContract = forall a. (MiningAlgorithm a) => MiningContract
{ contractHashrate :: Hashrate a
, contractCost :: Money USD
, contractExpiration :: Int
}
makeMiningContract :: (MiningAlgorithm a) => Hashrate a -> Money USD -> Int -> MiningContract
makeMiningContract = MiningContract
makeMiningContractSimple :: (MiningAlgorithm a) => Hashrate a -> MiningContract
makeMiningContractSimple h = makeMiningContract h (makeUSD 0) 0
instance Show MiningContract where
show (MiningContract h c e) = "MiningContract "
++ "{contractHashrate = " ++ show h ++ ", "
++ "contractCost = " ++ show c ++ ", "
++ "contractExpiration = " ++ show e ++ "}"
data UserAccount = UserAccount
{ accountBalance :: Money BTC
, accountContracts :: [MiningContract]
}
instance Show UserAccount where
show (UserAccount m cs) = "UserAccount {"
++ "accountBalance = " ++ show m ++ ", "
++ "accountContracts = " ++ show cs ++ "}"
makeUserAccount :: Money BTC -> [MiningContract] -> UserAccount
makeUserAccount = UserAccount
userAccountPayouts :: PayoutTable -> UserAccount -> [Money BTC]
userAccountPayouts t (UserAccount _ cs) = map (contractPayout t) cs
userAccountPayout :: PayoutTable -> UserAccount -> Money BTC
userAccountPayout t = (foldr (\m ma -> m ^+^ ma) (makeBTC 0)) . (userAccountPayouts t)
userAccountMEFs :: MEFTable -> UserAccount -> [Money USD]
userAccountMEFs t (UserAccount _ cs) = map (contractMEF t) cs
userAccountMEF :: MEFTable -> UserAccount -> Money USD
userAccountMEF t = (foldr (\m ma -> m ^+^ ma) (makeUSD 0)) . (userAccountMEFs t)
infoUserAccount :: UserAccount -> String
infoUserAccount (UserAccount m cs) = "HashFlare.io account, balance = " ++ show (amount m) ++ " BTC, contracts = " ++ show (length cs) ++ "\n"
++ "Total SHA256 hashrate = " ++ show (sha256r / tera) ++ " TH/s\n"
++ "Total Scrypt hashrate = " ++ show (scryptr / mega) ++ " MH/s\n"
++ "Total ETHASH hashrate = " ++ show (ethashr) ++ " H/s\n"
++ "Total X11 hashrate = " ++ show (x11r) ++ " H/s\n"
++ "Total EQUIHASH hashrate = " ++ show (equihashr ) ++ " H/s\n"
where hs = map (\(MiningContract h _ _) -> (typeOf (algorithm h), rate h)) cs
algosum algo = sum $ map snd $ filter (\talr -> fst talr == algo) hs
sha256r = algosum $ typeOf SHA256
scryptr = algosum $ typeOf Scrypt
ethashr = algosum $ typeOf ETHASH
x11r = algosum $ typeOf X11
equihashr = algosum $ typeOf EQUIHASH
type MEFTable = M.Map (TypeRep) (Money USD, Double)
makeMEFTable :: [(TypeRep, (Money USD, Double))] -> MEFTable
makeMEFTable = M.fromList
hashrateMEF :: MiningAlgorithm a => MEFTable -> Hashrate a -> Money USD
hashrateMEF t h = c
where al = (typeOf . algorithm) h
hr = rate h
c = case M.lookup al t of
Just (m, r) -> m ^* ((fromIntegral . truncate) (hr / r))
Nothing -> makeUSD 0
contractMEF :: MEFTable -> MiningContract -> Money USD
contractMEF t (MiningContract h _ _) = hashrateMEF t h
type PayoutTable = M.Map TypeRep (Money BTC, Double)
makePayoutTable :: [(TypeRep, (Money BTC, Double))] -> PayoutTable
makePayoutTable = M.fromList
hashratePayout :: MiningAlgorithm a => PayoutTable -> Hashrate a -> Money BTC
hashratePayout t h = c
where al = (typeOf . algorithm) h
hr = rate h
c = case M.lookup al t of
Just (m, r) -> m ^* (hr / r)
Nothing -> makeBTC 0
contractPayout :: PayoutTable -> MiningContract -> Money BTC
contractPayout t (MiningContract h _ _ ) = hashratePayout t h
defaultSHA256Contract = MiningContract (makeHashrate SHA256 (10 * giga)) (makeUSD 1.20) 0
defaultScryptContract = MiningContract (makeHashrate Scrypt (1 * mega)) (makeUSD 8.20) 0
defaultMEFTable = makeMEFTable
[ (typeOf SHA256, (makeUSD 0.004, 10 * giga))
, (typeOf Scrypt, (makeUSD 0.01, 1 * mega))
]