[Haskell-cafe] Type synonyms considered harmful?

Christopher Done chrisdone at gmail.com
Thu Jan 22 00:29:25 UTC 2015


Because that wouldn't show up in haddock or :t.

On 22 January 2015 at 01:23, <amindfv at gmail.com> wrote:

> Considering it doesnt give you any type safety, why not just write:
>
> foo (red :: Double) (green :: Double) (blue :: Double) = undefined
>
> Tom
>
>
> El Jan 21, 2015, a las 10:32, Niklas Haas <haskell at nand.wakku.to>
> escribió:
>
> >> 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
> >
> > In fact, why even bother with the explicit forall? Default behavior is
> > to universally quantify unused variable names, after all.
> >
> > {-# LANGUAGE TypeOperators #-}
> >
> > type (l ∷ t) = t
> >
> > foo :: (red ∷ Double) -> (green ∷ Double) -> (blue ∷ Double) -> IO ()
> >
> > At this point, I think this is a syntax form we can surely all agree
> upon.
> > _______________________________________________
> > Haskell-Cafe mailing list
> > Haskell-Cafe at haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
> _______________________________________________
> 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/20150122/a43324fa/attachment.html>


More information about the Haskell-Cafe mailing list