module Hack.Contrib.Constants where

import MPS.Light
import Prelude hiding ((.))
import Data.Map

status_with_no_entity_body :: [Int]
status_with_no_entity_body = [100 .. 199] ++ [204, 304]


-- header constants
_CacheControl                   :: String
_Connection                     :: String
_Date                           :: String
_Pragma                         :: String
_TransferEncoding               :: String
_Upgrade                        :: String
_Via                            :: String
_Accept                         :: String
_AcceptCharset                  :: String
_AcceptEncoding                 :: String
_AcceptLanguage                 :: String
_Authorization                  :: String
_Cookie                         :: String
_Expect                         :: String
_From                           :: String
_Host                           :: String
_IfModifiedSince                :: String
_IfMatch                        :: String
_IfNoneMatch                    :: String
_IfRange                        :: String
_IfUnmodifiedSince              :: String
_MaxForwards                    :: String
_ProxyAuthorization             :: String
_Range                          :: String
_Referer                        :: String
_UserAgent                      :: String
_Age                            :: String
_Location                       :: String
_ProxyAuthenticate              :: String
_Public                         :: String
_RetryAfter                     :: String
_Server                         :: String
_SetCookie                      :: String
_TE                             :: String
_Trailer                        :: String
_Vary                           :: String
_Warning                        :: String
_WWWAuthenticate                :: String
_Allow                          :: String
_ContentBase                    :: String
_ContentEncoding                :: String
_ContentLanguage                :: String
_ContentLength                  :: String
_ContentLocation                :: String
_ContentMD5                     :: String
_ContentRange                   :: String
_ContentType                    :: String
_ETag                           :: String
_Expires                        :: String
_LastModified                   :: String
_ContentTransferEncoding        :: String



_CacheControl                   =  "Cache-Control"        
_Connection                     =  "Connection"           
_Date                           =  "Date"                 
_Pragma                         =  "Pragma"               
_TransferEncoding               =  "Transfer-Encoding"    
_Upgrade                        =  "Upgrade"              
_Via                            =  "Via"                  
_Accept                         =  "Accept"               
_AcceptCharset                  =  "Accept-Charset"       
_AcceptEncoding                 =  "Accept-Encoding"      
_AcceptLanguage                 =  "Accept-Language"      
_Authorization                  =  "Authorization"        
_Cookie                         =  "Cookie"               
_Expect                         =  "Expect"               
_From                           =  "From"                 
_Host                           =  "Host"                 
_IfModifiedSince                =  "If-Modified-Since"    
_IfMatch                        =  "If-Match"             
_IfNoneMatch                    =  "If-None-Match"        
_IfRange                        =  "If-Range"             
_IfUnmodifiedSince              =  "If-Unmodified-Since"  
_MaxForwards                    =  "Max-Forwards"         
_ProxyAuthorization             =  "Proxy-Authorization"  
_Range                          =  "Range"                
_Referer                        =  "Referer"              
_UserAgent                      =  "User-Agent"           
_Age                            =  "Age"                  
_Location                       =  "Location"             
_ProxyAuthenticate              =  "Proxy-Authenticate"   
_Public                         =  "Public"               
_RetryAfter                     =  "Retry-After"          
_Server                         =  "Server"               
_SetCookie                      =  "Set-Cookie"           
_TE                             =  "TE"                   
_Trailer                        =  "Trailer"              
_Vary                           =  "Vary"                 
_Warning                        =  "Warning"              
_WWWAuthenticate                =  "WWW-Authenticate"     
_Allow                          =  "Allow"                
_ContentBase                    =  "Content-Base"         
_ContentEncoding                =  "Content-Encoding"     
_ContentLanguage                =  "Content-Language"     
_ContentLength                  =  "Content-Length"       
_ContentLocation                =  "Content-Location"     
_ContentMD5                     =  "Content-MD5"          
_ContentRange                   =  "Content-Range"        
_ContentType                    =  "Content-Type"         
_ETag                           =  "ETag"                 
_Expires                        =  "Expires"              
_LastModified                   =  "Last-Modified"        
_ContentTransferEncoding        =  "Content-Transfer-Encodeing"


-- mime type
_TextPlain                  :: String
_TextHtml                   :: String
_TextPlainUTF8              :: String
_TextHtmlUTF8               :: String

_TextPlain     = "text/plain"
_TextHtml      = "text/html"
_TextPlainUTF8 = "text/plain; charset=UTF-8"
_TextHtmlUTF8  = "text/html; charset=UTF-8"


-- status code
status_code :: Map Int String
status_code =
  [  x       100          "Continue"
  ,  x       101          "Switching Protocols"
  ,  x       200          "OK"
  ,  x       201          "Created"
  ,  x       202          "Accepted"
  ,  x       203          "Non-Authoritative Information"
  ,  x       204          "No Content"
  ,  x       205          "Reset Content"
  ,  x       206          "Partial Content"
  ,  x       300          "Multiple Choices"
  ,  x       301          "Moved Permanently"
  ,  x       302          "Found"
  ,  x       303          "See Other"
  ,  x       304          "Not Modified"
  ,  x       305          "Use Proxy"
  ,  x       307          "Temporary Redirect"
  ,  x       400          "Bad Request"
  ,  x       401          "Unauthorized"
  ,  x       402          "Payment Required"
  ,  x       403          "Forbidden"
  ,  x       404          "Not Found"
  ,  x       405          "Method Not Allowed"
  ,  x       406          "Not Acceptable"
  ,  x       407          "Proxy Authentication Required"
  ,  x       408          "Request Timeout"
  ,  x       409          "Conflict"
  ,  x       410          "Gone"
  ,  x       411          "Length Required"
  ,  x       412          "Precondition Failed"
  ,  x       413          "Request Entity Too Large"
  ,  x       414          "Request-URI Too Large"
  ,  x       415          "Unsupported Media Type"
  ,  x       416          "Requested Range Not Satisfiable"
  ,  x       417          "Expectation Failed"
  ,  x       500          "Internal Server Error"
  ,  x       501          "Not Implemented"
  ,  x       502          "Bad Gateway"
  ,  x       503          "Service Unavailable"
  ,  x       504          "Gateway Timeout"
  ,  x       505          "HTTP Version Not Supported"
  ] .to_h
  where x a b = (a, b)