[Haskell-cafe] Different return type?

John Ky newhoggy at gmail.com
Sun Jan 18 23:11:20 EST 2009


Hi Daniel,

When would I use either?  What are the trade-offs?

Thanks

-John

On Mon, Jan 19, 2009 at 1:13 PM, Daniel Fischer <daniel.is.fischer at web.de>wrote:

> Am Montag, 19. Januar 2009 02:44 schrieb John Ky:
> > Hi,
> >
> > Possibly a silly question but is it possible to have a function that has
> a
> > different return type based on it's first argument?
> >
> > For instance
> >
> > data Person = Person { name :: String, ... }
> > data Business = Business { business_number :: Int, ...}
> >
> > key person = name person
> > key business = business_number business
> >
> > Thanks
> >
> > -John
>
> Well, you could use
>
> {-# LANGUAGE MultiParamTypeClasses, FunctionalDependencies,
> TypeSynonymInstances #-}
> module Key where
>
> data Person = Person { name :: String }
> data Business = Business { business_number :: Int}
>
> class Key a b | a -> b where
>    key :: a -> b
>
> instance Key Person String where
>    key = name
>
> instance Key Business Int where
>    key = business_number
>
> or with type families:
> {-# LANGUAGE TypeFamilies #-}
> class Key2 a where
>    type Res a
>    key2 :: a -> Res a
>
> instance Key2 Person where
>    type Res Person = String
>    key2 = name
>
> instance Key2 Business where
>    type Res Business = Int
>    key2 = business_number
>
>
> but apart from that and parametrically polymorphic functions (of type a ->
> [a]
> or the like), I don't think it's possible, it would need dependent types.
>
> HTH,
> Daniel
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: http://www.haskell.org/pipermail/haskell-cafe/attachments/20090119/e00d18d7/attachment.htm


More information about the Haskell-Cafe mailing list