[Haskell] Re: Type Class Question

oleg at pobox.com oleg at pobox.com
Tue Nov 22 04:01:48 EST 2005


Paul Govereau wrote:
> BTW, The above program is a translation of an idiomatic use of
> functors in ML (pardon my syntax):
>
>   module A : sig type t = ... end
>   module B : funsig(X:SHOW where t = A.t) sig bar : A.t -> string end
>   module C : SHOW where t = A.t
>   open A
>   open B(C)

ML modules poorly correspond to Haskell modules. Rather, they
correspond to Haskell typeclasses:

{-# OPTIONS -fglasgow-exts #-}
{-# OPTIONS -fallow-undecidable-instances #-}

module Foo where

--   module A : sig type t = ... end
--   A is a constraint on type t
class A t
-- different instances of A will define what t actually means

--   module B : funsig(X:SHOW where t = A.t) sig bar : A.t -> string end
class (A t, Show t) => B t where
    bar :: t -> String

--   module C : SHOW where t = A.t
--   A restriction on Show such that its type parameter is constrained to
--   be in A
class (A t, Show t) => C t
instance (A t, Show t) => C t

--   open A
-- Perhaps some implementation of A must be provided somewhere...

--   open B(C)
instance C t => B t where
    bar = show


-- Eventually we need to give a structure that implements signature A
data X = X
instance A X
instance Show X where show _ = "X"

test = bar X



More information about the Haskell mailing list