[Haskell-cafe] Type synonyms considered harmful?

Jeremy Shaw jeremy at n-heptane.com
Wed Jan 21 15:25:50 UTC 2015


Now we're definitely getting somewhere! I'm not to thrilled about the use
of string literals though. How about this?

{-# LANGUAGE TypeOperators, DataKinds, RankNTypes #-}
type (l ∷ t) = t

foo :: forall red green blue. (red ∷ Double) -> (green ∷ Double) -> (blue ∷
Double) -> IO ()

We just need to patch hlint to make this the suggested style.

- jeremy

On Sun, Jan 18, 2015 at 7:05 PM, Niklas Haas <haskell at nand.wakku.to> wrote:

> On Mon, 19 Jan 2015 01:12:58 +0100, Christopher Done <chrisdone at gmail.com>
> wrote:
> > >
> > > foo : (x : Int) -> (y : Int) -> (red : Double) -> (blue : Double) ->
> > > (green : Double) -> IO ()
> > >
> > > And that will solve everything! What could possibly go wrong!
> > >
> >
> > How about a type-level the? =p
> >
> > type The label t = t
> >
> > foo :: The red Double -> The green Double -> The blue Double -> IO ()
> >
> > Or with polykinds:
> >
> > foo :: The "Red" Double -> The "Green" Double -> The "Blue" Double -> IO
> ()
>
> Clearly needs more TypeOperators.
>
> type (l ∷ t) = t
>
> foo :: ("red" ∷ Double) -> ("green" ∷ Double) -> ("blue" ∷ Double) -> IO ()
> _______________________________________________
> Haskell-Cafe mailing list
> Haskell-Cafe at haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
>
-------------- next part --------------
An HTML attachment was scrubbed...
URL: <http://www.haskell.org/pipermail/haskell-cafe/attachments/20150121/e2e647f2/attachment.html>


More information about the Haskell-Cafe mailing list