module Text.Language.Internals where
import Text.JSON.Generic
import Network.Curl
import qualified Data.List as L
import Prelude hiding ((.), ())
import Network.URI (isAllowedInURI)
import qualified Codec.Binary.UTF8.String as Utf
import Numeric
data RStatus = RStatus
  {
    responseStatus :: Integer
  }
  deriving (Eq, Show, Data, Typeable)
   
data RBad = RBad
  {
    responseDetails :: String
  }
  deriving (Eq, Show, Data, Typeable)
curl :: String -> IO (Maybe String)
curl x = do
  (r, s) <- curlGetString x []
  if r == CurlOK
    then return  Just s
    else return Nothing
google_api :: String -> [(String,String)] -> String
google_api base_url args = 
  let make_pair (x, y) = x ++ "=" ++ escape_uri y
  in
  base_url ++ "?" ++  args .map make_pair .join "&"
 
(.) :: a -> (a -> b) -> b
a . f = f a
infixl 9 .
() :: (a -> b) -> a -> b
f  x =  f x
infixr 0  
join :: [a] -> [[a]] -> [a]
join = L.intercalate
escape_uri :: String -> String
escape_uri = escapeURIString isAllowedInURI
escapeURIChar :: (Char->Bool) -> Char -> String
escapeURIChar p c
    | p c       = [c]
    | otherwise = concatMap ('%':) $ map (flip showHex "") $ Utf.encode [c]
escapeURIString
    :: (Char->Bool)     
                        
    -> String           
    -> String           
escapeURIString p s = concatMap (escapeURIChar p) s