module Network.Randomorg
( RNG(..)
, integers, shuffle, strings, quota
) where
import Control.Applicative ((<$>))
import Data.ByteString.Char8 (ByteString, readInteger, readInt)
import Data.List (intercalate)
import Data.Maybe (fromMaybe)
import Data.Word (Word8)
import Network.Curl
import Prelude hiding (max, min)
import qualified Data.ByteString.Char8 as B
data RNG = New
| Id String
| Date String
class Get α where
get ∷ α → String
getF ∷ (Functor μ, Get α) ⇒ μ α → μ String
getF = fmap get
instance Get Int where
get = show
instance Get Bool where
get True = "on"
get False = "off"
instance Get (Word8,Word8,Word8,Word8) where
get (α,β,γ,δ) = intercalate "." . map show $ [α,β,γ,δ]
instance Get RNG where
get New = "new"
get (Id s) = "id." ++ s
get (Date s) = "date." ++ s
integers ∷ Int
→ Int
→ Int
→ RNG
→ IO (Maybe [Int])
integers (get → n)
(get → min)
(get → max)
(get → rng) =
let url = "http://www.random.org/integers/?col=1&base=10&format=plain&"
params = zip ["num","min","max","rnd"] [n, min, max, rng]
in mapM (\l → fst <$> readInt l) . B.lines . respBody <$> query url params
shuffle ∷ Int
→ Int
→ RNG
→ IO (Maybe [Int])
shuffle min
max
(get → rng)
| max min + 1 <= 10000 =
let url = "http://www.random.org/sequences/?col=1&format=plain&"
params = zip ["min","max","rnd"] [get min, get max, rng]
in mapM (\l → fst <$> readInt l) . B.lines . respBody <$> query url params
| otherwise = return Nothing
strings ∷ Int
→ Int
→ Bool
→ Bool
→ Bool
→ Bool
→ RNG
→ IO [String]
strings (get → n)
(get → l)
(get → digits)
(get → upper)
(get → lower)
(get → unique)
(get → rng) =
let url = "http://www.random.org/strings/?format=plain&"
params = zip ["num","len","digits","upperalpha","loweralpha","unique","rnd"] [n, l, digits, upper, lower, unique, rng]
in map B.unpack . B.lines . respBody <$> query url params
quota ∷ Maybe (Word8, Word8, Word8, Word8)
→ IO (Maybe Integer)
quota (getF → ip) =
let url = "http://www.random.org/quota/?format=plain&"
params = zip ["ip"] [fromMaybe "" ip]
in (fst <$>) . readInteger . respBody <$> query url params
query ∷ String → [(String,String)] → IO (CurlResponse_ [(String, String)] ByteString)
query url (filter (not . null . snd) → params) =
let ua = "Mozilla/5.0 (X11; Linux x86_64; rv:10.0) Gecko/20100101 Firefox/10.0 Iceweasel/10.0"
in withCurlDo $ curlGetResponse_ (url ++ intercalate "&" (map (\(k,v) → k ++ "=" ++ v) params))
[ CurlFailOnError False
, CurlUserAgent ua
]