2010/1/14 Evan Laforge
Wow, that's kind of cute:
{-# LANGUAGE UnicodeSyntax #-} (*) = (*) (/) = (/) 公式 高 中 低 = 高 * 中 * 低 / 整數 整數 = 123
That code snippet is also perfectly legal Haskell without the UnicodeSyntax language extension. You use UnicodeSyntax if you want to write code like this: {-# LANGUAGE UnicodeSyntax, ScopedTypeVariables #-} swap ∷ ∀ α β. (α, β) → (β, α) swap = uncurry $ flip (,)
Oddly, if I change the order of these definitions I get syntax errors. Very mysterious. Nice how it knows that * is a symbol, but I'm not sure how I'm supposed to name a type.
I was a bit surprised that you could use * as an operator since it is a punctuation character. Maybe there are some corner cases with fullwidth characters or with composition of characters.
Unicode identifiers are fun but this is a good point. The line has to be somewhere, so it might as well be in the historical position unless there are widely agreed on benefits to moving it.
I have already crossed that line: http://hackage.haskell.org/package/base-unicode-symbols http://hackage.haskell.org/package/containers-unicode-symbols But I am aware that there is a point beyond which unicode symbols only make your code harder to understand. So I try to be conservative in my use of them. Still, there are a lot of useful and acceptable symbols which are not part of the historic ASCII set: ∈, ≤, ∪, ∧, ¬, ∘ to name a few.