[Haskell-beginners] Unicode Fanatic — How to use?

Brent Yorgey byorgey at seas.upenn.edu
Thu Mar 27 21:26:45 UTC 2014


Have you seen

  http://www.haskell.org/haskellwiki/Unicode-symbols ?

I think it answers most of your questions.  In brief: the
UnicodeSyntax pragma allows various non-ASCII symbols to be used in
place of built-in Haskell syntax (such as ∀ in place of forall).  The
base-unicode-symbols defines non-ASCII synonyms for common functions
defined in the 'base' package.  The two are entirely orthogonal: the
new names for things in 'base' have nothing to do with Haskell syntax;
conversely, Haskell with no extensions already supports arbitrary
Unicode in identifier names.

-Brent

On Thu, Mar 27, 2014 at 03:51:22PM -0500, John M. Dlugosz wrote:
> I love using non-ASCII characters!  Even my name, Długosz, needs
> Latin-2.  My wife's name, 涛, doesn't even use Latin characters.
> I've inserted thousands of em and en dashes in Wikipedia and can
> easily type at least three kinds of blank space.
> 
> When I was in a college class on programming theory, we studied
> Backus’s FP System and I corresponded with John Backus to ask a
> question the prof couldn't handle, and he sent me the TeX definitions
> he used, so my homework really did match the appearance of the
> textbook.  But that's another story.  I managed to get my name in the
> Unicode 3 hardcopy book.
> 
> So, I relish the ability to use proper math symbols in Haskell.
> 
> Here is an example of what I've tried:
> 
> 	{-# LANGUAGE UnicodeSyntax #-}
> 
> 	import Prelude.Unicode
> 
> 	f x y = x∨y
> 
> 	result = f ∘ id
> 
> 	-- problem = ¬ True
> 
> Is the UnicodeSyntax pragma a different mechanism than the modules?
> Do I need to state both, or do they clash, or work together, or what?
> 
> Do I need to list all the individual modules (up to 12 of them) as
> needed (see http://hackage.haskell.org/package/base-unicode-symbols)
> or can they be brought in as one easy chunk, as the package itself is
> one thing?
> 
> The compiler does not like the ¬ symbol, with or without the pragma.
> http://hackage.haskell.org/package/base-unicode-symbols-0.2.2.4/docs/Prelude-Unicode.html
> clearly shows it (the first one!) and it appears in the module source
> so presumably it didn't choke there.  I recall seeing that it is one
> of the "problematic" symbols but GHC has some extensions.
> 
> OTOH, I read that λ can’t be made to work, which is sad.  Maybe ⅄
> (which is a symbol) can be used instead?
> 
> _______________________________________________
> Beginners mailing list
> Beginners at haskell.org
> http://www.haskell.org/mailman/listinfo/beginners
> 


More information about the Beginners mailing list