[web-devel] Simple mime-type package

Peter Robinson thaldyron at gmail.com
Fri Apr 23 04:26:11 EDT 2010


On 22 April 2010 21:55, Jeremy Shaw <jeremy at n-heptane.com> wrote:
> On Apr 22, 2010, at 2:31 PM, Peter Robinson wrote:
>> To avoid the hard coding issue, why not simply introduce a MimeType type
>> class?
>
> What would this class do ?

If extensibility is the main concern, then something like:

{-# LANGUAGE FlexibleInstances #-}
{-# LANGUAGE MultiParamTypeClasses #-}
{-# LANGUAGE ScopedTypeVariables #-}
{-# LANGUAGE DeriveDataTypeable #-}
module Mime
where

import Data.Typeable
import Data.Convertible.Text

class ContentType t where
    typeByExt :: String -> t
    toString  :: t -> String

instance ContentType t => ConvertSuccess t [Char] where
  convertSuccess = toString

data TypeHtml = TypeHtml
  deriving(Typeable)

instance ContentType TypeHtml where
    typeByExt "html" = TypeHtml
    toString TypeHtml = "text/html; charset=utf-8"


-- Peter


More information about the web-devel mailing list