In most imperative languages understanding "x.name" requires knowledge of the type of x to understand what "name" refers to.

Now with TDNR in Haskell, "name x" requires knowledge of the type of x to understand what "name" refers to.

As a newcomer, I think some of the coding conventions favored by haskell-coders to be write-only, but in this case I wonder why this is less readable in Haskell than in, say C?

Alexander

On 10 November 2010 19:05, Albert Y. C. Lai <trebla@vex.net> wrote:
Typed-directed name resolution brings Haskell closer to a write-only language; that is, an ambiguous phrase made total sense to the author when the author wrote it, but an independent reader will need extraordinary effort to disambiguate.

{-# LANGUAGE TypeDirectedNameResolution #-}

import EnglishMonad
import Cities(buffalo)
import Animals(buffalo)
import Verbs(buffalo,buffalo)

{- why two buffalo's from Verbs? because they are of different types: one is present verb type and the other is past participle verb type. ever heard of Type Directed Name Resolution? -}

buffalo = buffalo buffalo buffalo buffalo buffalo buffalo buffalo buffalo

main = runEnglishMonad buffalo

{- http://en.wikipedia.org/wiki/Buffalo_buffalo_Buffalo_buffalo_buffalo_buffalo_Buffalo_buffalo -}

_______________________________________________
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe