module Web.Api.WebDriver.Uri (
Host()
, mkHost
, Port()
, mkPort
) where
import Test.QuickCheck
( Arbitrary(..), oneof, vectorOf, Positive(..) )
newtype Host = Host
{ unHost :: String
} deriving Eq
mkHost :: String -> Maybe Host
mkHost str =
if all (`elem` hostAllowedChars) str
then Just (Host str)
else Nothing
instance Show Host where
show = unHost
instance Arbitrary Host where
arbitrary = do
Positive k <- arbitrary
str <- vectorOf k $ oneof $ map return hostAllowedChars
case mkHost str of
Just h -> return h
Nothing -> error "In Arbitrary instance for Host: bad characters."
hostAllowedChars :: String
hostAllowedChars = concat
[ ['a'..'z'], ['A'..'Z'], ['0'..'9'], ['-','_','.','~','%'] ]
newtype Port = Port { unPort :: String }
deriving Eq
mkPort :: String -> Maybe Port
mkPort str =
if all (`elem` ['0'..'9']) str
then Just (Port str)
else Nothing
instance Show Port where
show = unPort
instance Arbitrary Port where
arbitrary = do
Positive k <- arbitrary
str <- vectorOf k $ oneof $ map return ['0'..'9']
case mkPort str of
Just p -> return p
Nothing -> error "In Arbitrary instance for Port: bad characters."