module Network.HTTP.Media.MediaType.Arbitrary () where
import Prelude hiding (concat)
import Control.Applicative ((<*>))
import Control.Monad (replicateM)
import Data.ByteString (append, concat, ByteString)
import Data.ByteString.Char8 (singleton)
import Data.Functor ((<$>))
import Network.HTTP.Media.MediaType ((/:), (//), MediaType)
import Test.QuickCheck (Arbitrary (arbitrary), choose, elements, Gen, listOf, oneof, sized)
instance Arbitrary MediaType where
arbitrary =
do n <- (//) <$> restrictedName <*> restrictedName
ps <- listOf $ (,) <$> restrictedName <*> restrictedName
return $ foldl (/:) n ps
restrictedName :: Gen ByteString
restrictedName = sized $ \ s ->
do n <- choose (0, min 126 s)
rs <- concat <$> replicateM n restrictedNameChar
(`append` rs) <$> restrictedNameFirst
restrictedNameFirst :: Gen ByteString
restrictedNameFirst = singleton <$> oneof [alpha, digit]
restrictedNameChar :: Gen ByteString
restrictedNameChar = singleton <$> oneof [ alpha
, digit
, elements ['!', '#', '$', '&', '-', '^', '_', '.', '+']
]
alpha :: Gen Char
alpha = elements $ ['a'..'z'] ++ ['A'..'Z']
digit :: Gen Char
digit = elements ['0'..'9']