[Haskell-cafe] ANNOUNCE: xmonad 0.7 released

2008-03-30 Thread Don Stewart

   http://xmonad.org

The xmonad dev team is pleased to announce xmonad 0.7!

The headlines:

The 0.7 release of xmonad provides several improvements over 0.6, including
improved integration with GNOME, more flexible "rules", various stability
fixes, and of course, many new and interesting features in the extension
library (general support for window decorations, utf8 support, scratch pad
terminals, pointer control) and more!

New GNOME support:

Active, automated support for GNOME utilities. We know our users
often like to use GNOME menus, tools and status bars, and we'd like
to announce that xmonad actively supports GNOME! Extensions for
communicating with and utilising gnome utilities come in the library
suite, as well as extensive documentation and support. For more information
see the GNOME/xmonad integration page on the wiki.

A period of active development:

In the past year, the xmonad development team received contributions
from over 60 developers, making xmonad one of the largest window
manager development teams around, and dwarfing other tiling window
manager projects. Yet, at the same time, the core code base remains at
around 1000 lines of code, with another 7000 lines in the extension
library -- a significant achievment!

Change logs:

http://haskell.org/haskellwiki/Xmonad/Notable_changes_since_0.6

http://xmonad.org/changelog-0.7.txt
http://xmonad.org/changelog-xmc-0.7.txt

About:

xmonad is a tiling window manager for X. Windows are arranged
automatically to tile the screen without gaps or overlap, maximising
screen use. Window manager features are accessible from the keyboard: a
mouse is optional. xmonad is extensible in Haskell, allowing for
powerful customisation. Custom layout algorithms, key bindings and other
extensions may be written by the user in config files. Layouts are
applied dynamically, and different layouts may be used on each
workspace. Xinerama is fully supported, allowing windows to be tiled on
several physical screens.

Features:

   * Very stable, fast, small and simple.
   * Automatic window tiling and management
   * First class keyboard support: a mouse is unnecessary
   * Full support for tiling windows on multi-head displays
   * Full support for floating, tabbing and decorated windows
   * Full support for Gnome and KDE utilities
   * XRandR support to rotate, add or remove monitors
   * Per-workspace layout algorithms
   * Per-screens custom status bars
   * Compositing support
   * Powerful, stable customisation and reconfiguration
   * Large extension library
   * Excellent, extensive documentation
   * Large, active development team, support and community

Get it!

Information, screenshots, documentation, tutorials and community
resources are available from the xmonad home page:

http://xmonad.org

The 0.7 release, and its dependencies, are available from 
hackage.haskell.org:

http://hackage.haskell.org/cgi-bin/hackage-scripts/package/xmonad

xmonad packages are available in the package systems of at least:

Debian, Gentoo, Arch, Ubuntu, OpenBSD,
NetBSD, FreeBSD, Gobo, NixOS, Source Mage, Slackware

and 0.7 packages will appear in coming days (some are already available).

On the fly updating to xmonad 0.7 is supported. You should be able
to upgrade to xmonad 0.7 from 0.6 and earlier, transparently,
without losing your session. Load the new code with mod-q and enjoy.

Extensions:

xmonad comes with a huge library of extensions (now more than 7
times the size of xmonad itself), contributed by viewers like you.

Extensions enable pretty much arbitrary window manager behaviour to
be implemented by users, in Haskell, in the config files.
For more information on using and writing extensions see the webpage.
The library of extensions is available from hackage:


http://hackage.haskell.org/cgi-bin/hackage-scripts/package/xmonad-contrib

Full documentation for using and writing your own extensions:

http://xmonad.org/contrib.html

This release brought to you by the xmonad dev team:

Spencer Janssen Don Stewart
Jason Creighton David Roundy
Brent YorgeyDevin Mullins 
Braden Shepherdson  Roman Cheplyaka
Lucas Mai

Featuring code contributions from over 60 developers:

Aaron DenneyAdam Vogt
Alec Berryman   Alex Tarkovsky
Alexandre BuisseAndrea Rossato
Austin SeippBas van Dijk
Ben VouiBrandon Allbery
Chris Mears Christian Thiemann
Clemens Fruhwirth   Daniel Neri
Daniel Wagner   Dave Harrison
David Glasser   David Lazar
Dmitry KurochkinDominik Bruhn
Dougal Stanton  Eric Mertens
Ferenc Wagner   Gwern Branwen
Hans Phil

Re: [Haskell-cafe] Equality constraints in type families

2008-03-30 Thread Manuel M T Chakravarty

Hugo Pacheco:
Yes, but doesn't the confluence problem only occur for type synonyms  
that ignore one or more of the parameters? If so, this could be  
checked...


You can't check this easily (for the general case).

Given

  type family G a b
  type FList a x = G a x
  type instance F [a] = FList a

Does FList ignore its second argument?  Depends on the type instances  
of G.


Manuel




On Fri, Mar 28, 2008 at 12:04 AM, Manuel M T Chakravarty <[EMAIL PROTECTED] 
> wrote:

Hugo Pacheco:
> Sorry, I meant
>
> type FList a x = Either One (a,x)
> type instance F [a] = FList a

We should not allow such programs.

Manuel

>
>
> On Thu, Mar 27, 2008 at 4:45 PM, Hugo Pacheco <[EMAIL PROTECTED]>
> wrote:
>
>
> The current implementation is wrong, as it permits
>
>   type S a b = a
>   type family F a :: * -> *
>   type instance F a = S a
>
> Why do we need to forbid this type instance?  Because it breaks the
> confluence of equality constraint normalisation.  Here are two
> diverging normalisations:
>
>   (1)
>
> F Int Bool  ~  F Int Char
>
>   ==> DECOMP
>
> F Int ~ F Int, Bool ~ Char
>
>   ==> FAIL
>
>
>   (2)
>
> F Int Bool  ~  F Int Char
>
>   ==> TOP
>
> S Int Bool  ~  S Int Char
>
>   ==> (expand type synonym)
>
> Int  ~  Int
>
>   ==> TRIVIAL
>
> This does mean that a program such as
>
> type FList a = Either One ((,) a)
> type instance F [a] = FList a
>
> will be disallowed in further versions?
> Doesn't this problem occur only for type synonyms that ignore one or
> more of the parameters? If so, this could be checked...
>
> hugo
>
>




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


Re: [Haskell-cafe] Equality constraints in type families

2008-03-30 Thread Hugo Pacheco
On Sun, Mar 30, 2008 at 3:54 AM, Manuel M T Chakravarty <
[EMAIL PROTECTED]> wrote:

> Hugo Pacheco:
> > Yes, but doesn't the confluence problem only occur for type synonyms
> > that ignore one or more of the parameters? If so, this could be
> > checked...
>
> You can't check this easily (for the general case).
>

I was most interested in knowing that this assumption was enough, and it
looks like it does.


>
> Given
>
>   type family G a b
>type FList a x = G a x
>type instance F [a] = FList a
>
> Does FList ignore its second argument?  Depends on the type instances
> of G.
>
> Manuel
>

I haven't thought of that, thanks for the example.

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


Re: [Haskell-cafe] Equality constraints in type families

2008-03-30 Thread Hugo Pacheco
Anyway, do you think it is feasible to have a flag such as
-fallow-unsafe-type-families for users to use at their own risk? (supposing
we know how to guarantee these constraints).
I speak for my own, there are currently some nice thinks that I can only
accomplish with partially applied type synonyms in type families, otherwise
code starts to get dummier in terms of type contexts and context variables.

Thanks,
hugo

On Sun, Mar 30, 2008 at 4:14 AM, Hugo Pacheco <[EMAIL PROTECTED]> wrote:

> On Sun, Mar 30, 2008 at 3:54 AM, Manuel M T Chakravarty <
> [EMAIL PROTECTED]> wrote:
>
> > Hugo Pacheco:
> > > Yes, but doesn't the confluence problem only occur for type synonyms
> > > that ignore one or more of the parameters? If so, this could be
> > > checked...
> >
> > You can't check this easily (for the general case).
> >
>
> I was most interested in knowing that this assumption was enough, and it
> looks like it does.
>
>
> >
> > Given
> >
> >   type family G a b
> >type FList a x = G a x
> >type instance F [a] = FList a
> >
> > Does FList ignore its second argument?  Depends on the type instances
> > of G.
> >
> > Manuel
> >
>
> I haven't thought of that, thanks for the example.
>
> hugo
>
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] compilation succeeds -- execution fails

2008-03-30 Thread Jason Dusek
Bertram Felgenhauer <[EMAIL PROTECTED]> wrote:
> Jason Dusek wrote:
>  >   It compiles fine and loads fine -- but it doesn't run fine:
>  > unknown symbol `___stginit_cedictzm0zi1zi1_DataziCharziCEDICTziMatter_'
>
>  This is a cabal pitfall.

  Thank you -- this tip saved my bacon.

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


Re: [Haskell-cafe] compilation succeeds -- execution fails

2008-03-30 Thread Jason Dusek
Stefan O'Rear <[EMAIL PROTECTED]> wrote:
>  The only type that you are allowed to assume corresponds to a C int is
>  CInt, in the Foreign.C.Types module.  This probably isn't the problem,
>  but it could make problems of its own on a 64-bit or otherwise weird
>  system.

  So say I turn everything back to pointers to CInt, what is the
  accepted way to convert from CInt to Int and CInt to Char? Is
  relying on the fact that CInt always wraps a Haskell integer
  an okay way to go? I might was well learn these things now,
  before I get into bad habits.

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


[Haskell-cafe] announce: hgdbmi (GDB/MI interface)

2008-03-30 Thread Evan Martin
Just in case someone else needed this, here you go:

GDB/MI lets programs drive GDB. It can be used, for example, by GDB
frontends. This module wraps attaching GDB to a process and parsing
the (surprisingly complicated) GDB/MI output.
http://hackage.haskell.org/cgi-bin/hackage-scripts/package/hgdbmi
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] compilation succeeds -- execution fails

2008-03-30 Thread Stefan O'Rear
On Sat, Mar 29, 2008 at 10:21:32PM -0700, Jason Dusek wrote:
> Stefan O'Rear <[EMAIL PROTECTED]> wrote:
> >  The only type that you are allowed to assume corresponds to a C int is
> >  CInt, in the Foreign.C.Types module.  This probably isn't the problem,
> >  but it could make problems of its own on a 64-bit or otherwise weird
> >  system.
> 
>   So say I turn everything back to pointers to CInt, what is the
>   accepted way to convert from CInt to Int

Same as any other pair of whole-number types - fromIntegral.

>   and CInt to Char?

fromIntegral and toEnum

>   Is relying on the fact that CInt always wraps a Haskell integer an
>   okay way to go?

What do you mean by wraps?  It's an opaque type...

Stefan


signature.asc
Description: Digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Parsec Expected Type

2008-03-30 Thread Tillmann Rendel
Paul Keir wrote: 
> What I'd like is to parse either the string "parameter", or the 
> string ":". I'm using 'reserved' and 'symbol' because they seem to 
> correspond well to the concepts in the language I'm parsing. 

You may consider using reservedOp for ":", depending on how ":+" should be 
parsed:

  for ":+" use reservedOp
  for ":" "+" use symbol

If you use reserved, then ":name" will be parsed as ":name" not ":" "name" as 
you probably expect. generally, reserved is for identifier-like keywords, and 
reservedOp for operator-like keywords.

> Perhaps I'd express my confusion better if I ask: Why are 'reserved'
> and 'symbol' different types?

I have no idea. They aren't in the Parsec manual on Daans site:

  http://legacy.cs.uu.nl/daan/download/parsec/parsec.html

You can fix this by defining

  reserved name = ParsecToken.reserved tokenParser name >> return name

instead of

  reserved = ParsecToken.reserved tokenParser

to "import" the reserved component from the tokenParser to the toplevel.
Now,

  reserved :: String -> CharParser st String

Another option is to fix it the other way, by defining

  symbol name = ParsecToken.symbol tokenParser name >> return ()

or to fix it in a ad-hoc manner, by defining

  ignored = (>> return ())

and using it in the approbiate places, like

  parameterOrColon = reserved "parameter" <|> ignored (symbol ":")

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


Re: [Haskell-cafe] [GSoC] Porting HaRe to use the GHC API

2008-03-30 Thread Jules Bean

Chaddaï Fouché wrote:

Comments, reactions ? You can also propose refactoring, if I complete
the port early, I'll try to add some refactoring to HaRe.


Comment: Yes please

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


Re: [Haskell-cafe] Re: HTTP client libraries

2008-03-30 Thread Iavor Diatchki
Hi,

On Fri, Mar 28, 2008 at 6:42 AM, John Goerzen <[EMAIL PROTECTED]> wrote:
> On 2008-03-28, Don Stewart <[EMAIL PROTECTED]> wrote:
>  > paulrbrown+haskell-cafe:
>
> > And we have a curl binding, already in wide use.
>  >
>  > http://code.haskell.org/curl.git/
>  >
>  > a release to hackage is imminent.
>
>  Do you mean this?
>
>  http://hackage.haskell.org/cgi-bin/hackage-scripts/package/curl-1.3.1
>
>  Looks like it's not quite as current as your Git repo.

Is this surprising?  Hackage is not a revision control system.
The curl package on hackage is a fairly recent version of the git repo.

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


Re: [Haskell-cafe] compilation succeeds -- execution fails

2008-03-30 Thread Claude Heiland-Allen

Jason Dusek wrote:

Stefan O'Rear <[EMAIL PROTECTED]> wrote:

 The only type that you are allowed to assume corresponds to a C int is
 CInt, in the Foreign.C.Types module.  This probably isn't the problem,
 but it could make problems of its own on a 64-bit or otherwise weird
 system.


  So say I turn everything back to pointers to CInt, what is the
  accepted way to convert from CInt to Int and CInt to Char?


Type class methods:

-- for numbers like Int, CInt
fromIntegral :: (Num b, Integral a) => a -> b

-- for Char
fromEnum :: (Enum a) => a -> Int
toEnum :: (Enum a) => Int -> a

>   Is

  relying on the fact that CInt always wraps a Haskell integer
  an okay way to go?


I don't know what you mean by this.

>   I might was well learn these things now,

  before I get into bad habits.


Hope this helps,


Claude
--
http://claudiusmaximus.goto10.org
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] compilation succeeds -- execution fails

2008-03-30 Thread Jonathan Cast

On 29 Mar 2008, at 10:21 PM, Jason Dusek wrote:

Stefan O'Rear <[EMAIL PROTECTED]> wrote:
 The only type that you are allowed to assume corresponds to a C  
int is
 CInt, in the Foreign.C.Types module.  This probably isn't the  
problem,

 but it could make problems of its own on a 64-bit or otherwise weird
 system.


  So say I turn everything back to pointers to CInt, what is the
  accepted way to convert from CInt to Int


Use fromIntegral to go CInt -> Int, Int -> CInt.  This only depends  
on CInt being an Integral type.



and CInt to Char?


Use toEnum . fromIntegral

jcc

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


Re: [Haskell-cafe] announce: Glome.hs raytracer

2008-03-30 Thread Ian Lynagh
On Thu, Mar 27, 2008 at 02:49:35AM +, Ian Lynagh wrote:
> On Wed, Mar 26, 2008 at 02:33:20PM -0700, Jim Snow wrote:
> > 
> > -Memory consumption is atrocious: 146 megs to render a scene that's a 
> > 33k ascii file.  Where does it all go?  A heap profile reports the max 
> > heap size at a rather more reasonable 500k or so.  (My architecture is 
> > 64 bit ubuntu on a dual-core amd.)
> 
> I haven't looked properly yet, but it looks like something is leaking
> memory that shouldn't be.

Bug filed here:

http://hackage.haskell.org/trac/ghc/ticket/2185


Thanks
Ian

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


[Haskell-cafe] Announce: Decimal arithmetic package

2008-03-30 Thread Paul Johnson
I've just uploaded version 0.1.0 of a decimal arithmetic package to 
Hackage.  Decimal numbers are stored as an Integral mantissa and a Word8 
exponent, where the number stored is mantissa * 10^(-exponent).  In 
other words the exponent is the number of decimal places stored.  There 
are also routines for partitioning a value such that the sum of the 
parts is equal to the original value.  This is useful in financial 
arithmetic.


This came out of my ongoing work on an AMQP binding for Haskell.  
Version 0-10 of the AMQP spec includes decimal fractions defined in this 
way for financial applications, so I thought I'd make a proper job of it.


A darcs repository will be set up shortly.

Paul.

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


Re: [Haskell-cafe] Monad instance for Data.Set

2008-03-30 Thread Henning Thielemann


On Tue, 25 Mar 2008, Ryan Ingram wrote:


settest :: S.Set Int
settest = runSetM $ do
   x <- mplus (mplus mzero (return 2)) (mplus (return 2) (return 3))
   return (x+3)
-- fromList [5,6]


What this does under the hood is treat the computation on each element of the
set separately, except at programmer-specified synchronization points where
the computation result is required to be a member of the Ord typeclass.


It's like working in the List monad mainly, collapsing duplicates from 
time to time, right?

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


[Haskell-cafe] Usage of Read Class

2008-03-30 Thread Simeon Mattes

Hello,

I would like to ask something that results in when I have the following
commands
data Color = Red | Green | Blue | Indigo | Violet deriving (Enum,Show,Read)
(read.show) x

:1:1:
Ambiguous type variable `a' in the constraint:
  `Read a' arising from a use of `read' at :1:1-4
Probable fix: add a type signature that fixes these type variable(s)

I also receive the same message with the following:

*Test > let x = Branch (Branch (Branch (Leaf 'a') (Leaf 'b')) (Leaf 'c') )
(Leaf 'd')
*Test > x
<<<'a'|'b'>|'c'>|'d'>
*Test > (read.show) x
:1:1:
Ambiguous type variable `a' in the constraint:
  `Read a' arising from a use of `read' at :1:1-4
Probable fix: add a type signature that fixes these type variable(s)


data Tree a = Leaf a | Branch (Tree a) (Tree a)
--type ShowS = String -> String
showsTree :: (Show a) => Tree a -> ShowS
showsTree (Leaf x) = shows x
showsTree (Branch l r) = ('<':).showsTree l . ('|':) . showsTree r . ('>':)

--type ReadS a = String -> [(a,String)]
readsTree :: (Read a) => ReadS (Tree a)
readsTree s = [(Branch l r, x) | ("<",t) <- lex s,
 (l,u) <-  readsTree t,
 ("|",v) <- lex u,
 (r,w) <- readsTree v,
 (">",x) <-lex w]
  ++
  [(Leaf x, t) | (x,t) <- read s]

instance Show a=> Show (Tree a) where
showsPrec _ x = showsTree x
   
instance Read a => Read (Tree a) where
readsPrec _ s = readsTree s


Why is this happen?  Maybe an example with a simple application of the Class
Read would be helpful.

Thanks

-- 
View this message in context: 
http://www.nabble.com/Usage-of-Read-Class-tp16381441p16381441.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


[Haskell-cafe] lexicographic order

2008-03-30 Thread Simeon Mattes

Hello everyone,

I would like to ask something that I found in the ebook "a Gentle
Introduction to Haskell".
http://haskell.org/tutorial/stdclasses.html#sect8.4

data Tree a = Leaf a | Branch (Tree a) (Tree a)
instance  (Ord a) => Ord (Tree a)  where
(Leaf _) <= (Branch _)  =  True
(Leaf x) <= (Leaf y)=  x <= y
(Branch _)   <= (Leaf _)=  False
(Branch l r) <= (Branch l' r')  =  l == l' && r <= r' || l <= l'

The latter specifies a lexicographic order: Constructors are ordered by the
order of their appearance the data declaration, and the arguments of a
constructor are compared from left to right.

Although I have tried to make sense what lexicographic order means I haven't
figured out. Maybe an example with a simple application of this would be
helpful. To be honest I can't understand what the symbol <= really means.


Thanks

-- 
View this message in context: 
http://www.nabble.com/lexicographic-order-tp16381434p16381434.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


Re: [Haskell-cafe] Usage of Read Class

2008-03-30 Thread Niklas Broberg
>  I would like to ask something that results in when I have the following
>  commands
>  data Color = Red | Green | Blue | Indigo | Violet deriving (Enum,Show,Read)
>  (read.show) x
>
>  :1:1:
> Ambiguous type variable `a' in the constraint:
>   `Read a' arising from a use of `read' at :1:1-4
> Probable fix: add a type signature that fixes these type variable(s)

What the error message says is, it doesn't know which type to read to.
read has the type Read a => String -> a, and unless you tell it what
'a' is going to be, how would it know? If you say '(read.show) x ::
Color' it should work just fine.

Cheers,

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


Re: [Haskell-cafe] lexicographic order

2008-03-30 Thread Niklas Broberg
>  Although I have tried to make sense what lexicographic order means I haven't
>  figured out. Maybe an example with a simple application of this would be
>  helpful. To be honest I can't understand what the symbol <= really means.

<= means "less than or equal to".

Normally, lexicograpic order is the order in which words would appear
in a lexicon. This can be generalized to other data types than strings
by the kind of comparison done here, by specifying an ordering of the
constructors (in this case Leaf < Branch).

Cheers,

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


Re: [Haskell-cafe] lexicographic order

2008-03-30 Thread Bulat Ziganshin
Hello Simeon,

Monday, March 31, 2008, 12:45:54 AM, you wrote:

> The latter specifies a lexicographic order: Constructors are ordered by the
> order of their appearance the data declaration, and the arguments of a
> constructor are compared from left to right.

> Although I have tried to make sense what lexicographic order means I haven't
> figured out. Maybe an example with a simple application of this would be
> helpful. To be honest I can't understand what the symbol <= really means.

i'm not sire that i understood your question (are you really never
seen less-or-equal comparison? :), but i can say about lex. order:

if you can compare chars and 'a' < 'b', then *lists* of chars compared
in lexicographic order will be

"aaa" < "aab"
"aab" < "aba"
"baa" < "abb"

and so on - i.e. it finds *left-most* pair of non-equal chars and returns
result based on it comparison

the same principle used for comparison of these trees - any Leaf
smaller than any Branch, if the same constructors are used then their
parameters are compared, from left to right

although the last alternative,

   (Branch l r) <= (Branch l' r')  =  l == l' && r <= r' || l <= l'

seems suspicious to me. isn't it the same as

   (Branch l r) <= (Branch l' r')  =  l <= l'

?




-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] Usage of Read Class

2008-03-30 Thread Ariel J. Birnbaum
> >  :1:1:
> > Ambiguous type variable `a' in the constraint:
> >   `Read a' arising from a use of `read' at :1:1-4
> > Probable fix: add a type signature that fixes these type variable(s)
>
> What the error message says is, it doesn't know which type to read to.
> read has the type Read a => String -> a, and unless you tell it what
> 'a' is going to be, how would it know? If you say '(read.show) x ::
> Color' it should work just fine.

Just to sharpen the point: read cannot know from the string it processes which 
type to deliver.

For example, try the following at the ghci prompt:

read "3"  -> Yields the same error as above
read "3" + 3  -> 6
read "3" + 3.3-> 6.3
read "3.3" + 3.3  -> 6.6
read "3.3" + 3-> Error: no parse

What's happening is that the type of the expression is determined by the 
literal on the _right_side_ of the + sign, and not by the contents of the 
string on the left side.

The last example is a bit tricky. ghci sees 3 on the rhs, which can be of any 
type in the Num class (as opposed to 3.3, which has to be of a Fractional 
type). If unresolved, it will default to Integer (or Int?), and try to 
parse "3.3" as such -- which will of course fail.

-- 
Ariel J. Birnbaum
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] lexicographic order

2008-03-30 Thread Bulat Ziganshin
Hello Bulat,

Monday, March 31, 2008, 1:16:35 AM, you wrote:

> if you can compare chars and 'a' < 'b', then *lists* of chars compared
> in lexicographic order will be

> "aaa" < "aab"
> "aab" < "aba"
> "baa" < "abb"

as it was mentioned by Niklas Broberg, the last sentence should be reversed:

"abb" < "baa"

sorry for +1 confusion :)


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] lexicographic order

2008-03-30 Thread Chaddaï Fouché
2008/3/30, Bulat Ziganshin <[EMAIL PROTECTED]>:
>  although the last alternative,
>(Branch l r) <= (Branch l' r')  =  l == l' && r <= r' || l <= l'
> seems suspicious to me. isn't it the same as
>(Branch l r) <= (Branch l' r')  =  l <= l'

Yes, it should be :
(Branch l r) <= (Branch l' r')  =  l < l' || l == l' && r <= r'

Lexical order for a tuple (a,b) is :
(a,b) <= (a',b') iff (a < a' or (a == a' and b <= b'))
The same idea can be applied to list (where Nil is strictly less than
anything else) or other datatypes.

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


Re: [Haskell-cafe] compilation succeeds -- execution fails

2008-03-30 Thread Jason Dusek
Thanks for your answers, everybody.

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


Re: [Haskell-cafe] Monad instance for Data.Set

2008-03-30 Thread Ryan Ingram
On Sun, Mar 30, 2008 at 1:09 PM, Henning Thielemann
<[EMAIL PROTECTED]> wrote:
>  It's like working in the List monad mainly, collapsing duplicates from
>  time to time, right?

Sort of.  You can look at it that way and get a basic understanding of
what's going on.

A slightly more accurate analysis of what is going on is that it is
working in ContT Set for a variation of ContT that doesn't require the
underlying object to be a full monad, but only a restricted one.

In such a monad you could define
> mplus :: ContT Set a -> ContT Set a -> ContT Set a
> mplus x y = lift $ union (runContT x id) (runContT y id)
(not valid haskell code)

However, what is actually happening is that we are defining a set of
"side-effectful" computations using Prompt, and then observing those
computations in a "Set" environment.  With this definition you can
actually implement the interface for any monad you want; just define
the operations in your data type.  In this case:

> data OrdP m a where
>PZero :: OrdP m a
>PRestrict :: Ord a => m a -> OrdP m a
>PPlus :: Ord a => m a -> m a -> OrdP m a

> type SetM = RecPrompt OrdP

Every monad provides at least the same operations as the Identity
monad; this definition says that SetM is a monad that provides those
operations, plus three additional operations: "prompt PZero", "prompt
$ PRestrict x", and "prompt $ PPlus x y" of the types shown in the
definition of "OrdP".

You can then interpret those operations however you want; runSetM
defines an observation function that runs the computation and returns
its results in a Set, given the restriction that the computation
itself returns an Ord type.

In order to really understand this, you need to understand the type of
"runPromptC":

runPromptC ::
(r -> ans)  -- "pure" result handler
-> (forall a. p a -> (a -> ans) -> ans) -- "side effect" handler
that gets a continuation
-> Prompt p r -- computation to run
-> ans

"runPromptC" is (almost) just the case operation for a structure of this type:

data Prompt p r =
Return r
| forall a. BindEffect (p a) (a -> Prompt p r)

except with the recursive call to runPromptC inlined within
BindEffect; given this data type you can define runPromptC easily:

runPromptC ret _ (Return r) = ret r
runPromptC _ prm (BindEffect p k) = prm p (\a -> runPromptC ret prm (k a))

This definition makes it obvious that the "pure" continuation "ret" is
called at the end of the computation, and the "effectful" continuation
prm is called to handle any side effects.

Exercise 1: Define the function "prompt :: p a -> Prompt p a" on this datatype.
Exercise 2: Define an instance of Monad for this datatype.

Now you should be able to understand the observation function "runSetM":

> runSetM :: Ord r => SetM r -> S.Set r
> runSetM = runPromptC ret prm . unRecPrompt where
>-- ret :: r -> S.Set r
>ret = S.singleton
>-- prm :: forall a. OrdP SetM a -> (a -> S.Set r) -> S.Set r
>prm PZero _ = S.empty
>prm (PRestrict m) k = unionMap k (runSetM m)
>prm (PPlus m1 m2) k = unionMap k (runSetM m1 `S.union` runSetM m2)

"ret" handles the result of pure computations; that is, those that
could have just as easily run in the Identity monad.  "prm" handles
any effects; in this case the three effects "PZero", "PRestrict" and
"PPlus".

You could write a different observation/interpretation function that
treated the elements as a List, or Maybe, or whatever.

Let me know if this makes sense, or if you have any other questions.

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


[Haskell-cafe] Possible to automatically determine typeclass membership?

2008-03-30 Thread Ryan Ingram
Is it possible in Haskell + GHC extensions to use reflection
techniques to determine typeclass membership?  I'm thinking of things
like the following:

Idea 1:

> data MaybeEq a = NoEq a | Eq a => HasEq a
> checkEq :: (some typeclass constraint) => a -> MaybeEq a

(such that checkEq x returns HasEq x if and only if x has an Eq instance.)

Idea 2:

> data HTrue
> data HFalse

> class MaybeEq a b | a -> b

> instance Eq a => MaybeEq a HTrue
> instance (otherwise) => MaybeEq a HFalse

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


Re: [Haskell-cafe] Functional dependencies with Type Classes

2008-03-30 Thread Manuel M T Chakravarty

Henning Günther:

suppose there are two (identical) classes:


class Res a b | a -> b  where
getRes :: a -> b


and


class Res2 t where
type Member t
getRes2 :: t -> Member t


It is easy to automatically make every instance of Res2 an instance of
res:


instance Res2 a => Res a (Member a) where
getRes x = getRes2 x


However, declaring every instance of Res an instance of Res2 seems
impossible, as the following doesn't compile


instance Res a b => Res2 a where
type Member a = b
getRes2 x = getRes x


Question is: How to do this? The reason I need it is because I use a
library which uses functional dependencies, but my classes shall be  
type

families.


The last definition is invalid as the right-hand side of a type family  
instance can only depend on its parameters.  However, in


  type Member a = b

you pull 'b' out of thin air.  Remember that associated types (ie,  
type families as part of classes) are only syntactic sugar for sparate  
type family and class declarations.  Obviously, it would be imposible  
to pull the type instance out of the class in your definition.  (The  
mismatch between FDs and TFs here really is due to FDs being tied to  
classes and TFs being separable - in that sense TFs are more general  
than FDs, and hence, you cannot always simulate TFs with FDs.)


However, you can wrap an FD library into a TF interface with some  
additional effort.  Using your example for illustration, define the  
type family and class separately:


  type family Member a
  class Res2 a where
getRes2 :: a -> Member a

Then, implement the catch all class instance as follows:

  instance Res a (Member a) => Res2 a where
getRes2 x = getRes x

(This needs -fundecidable-instances.  It is perfectly decidable if  
your FD class is, but GHC doesn't know that.)


Now, the additional overhead is that you need to define the type  
family instances separately; ie, for every class instance of the FD  
class, such as


  instance Res Int Bool where
getRes x = x == 0

you need to repeat the type mapping:

  type instance Member Int = Bool

I hope this is not too much of a burden in your application.

Manuel

PS: Hmm, maybe this should go onto the 
wiki...___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Wumpus World

2008-03-30 Thread Richard A. O'Keefe

On 28 Mar 2008, at 10:59 pm, Benjamin L. Russell wrote:

The commercial SICStus Prolog is also substantially
more expensive (see
http://www.sics.se/isl/sicstuswww/site/index.html), at
153 euros for a Personal License (see
http://www.sics.se/isl/sicstuswww/site/order4.html).
Prices for Academic, Single-User Commercial, and
Multi-User Commercial licenses are even more
expensive, at 1560, 1980, and 7800 euros,
respectively.  An Evaluation License is only valid for
30 days.

Not all students and researchers can afford a Personal
License.


Let me contrast SICStus Prolog with GHC.
I *have* a personal copy of SICStus on my SunBlade 100/Solaris 2.10
system which installed absolutely trouble free.
I *did* have a copy of GHC, but trying to install GHC 6.4 took
a great deal of my time and now I don't have a working GHC any more.
So for me, GHC is by far the more expensive: I've spent considerably
more than 500 Euros of my time and got nothing for it.  Much though
I admire Jan, I've also had such a lot of trouble installing SWI Prolog
on various machines that SICStus was *really* cheaper than the "free"
Prolog after all.  I do wish people would remember that not all the
world is Linux.

153 Euros (why did the Europeans name their currency after the
Common Wallaroo?) is NZD 303 or about the price of two textbooks.
(Three copies of Bird's introduction to functional programming
would do it, if they shipped free.)

You're telling me that *researchers* can't afford the price of
a couple of books?

The academic licence isn't that unreasonable.  1560 Euros is
NZD 3091, which is about one month of a TA's pay.  Another 880
Euros gives you the right to give your students free binaries,
however many students you have, year after year after year.


 Can you recommend an alternative, fast
Prolog development system under a free licensing
agreement, such as GPL/GLPL?


There is, after all, GNU Prolog.  The last time I saw any benchmarks,
it was substantially faster than SWI, while not quite as good as  
SICStus.


See http://gprolog.inria.fr/ or http://www.gprolog.org/

For what it's worth, GNU Prolog's developers *do* realise that not all
the world's linux.


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


Re: [Haskell-cafe] Equality constraints in type families

2008-03-30 Thread Manuel M T Chakravarty

Hugo Pacheco:
Anyway, do you think it is feasible to have a flag such as -fallow- 
unsafe-type-families for users to use at their own risk? (supposing  
we know how to guarantee these constraints).


Sorry, but it doesn't seem like a good idea to enable an unsound type  
system even by an explicit option.


Manuel

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


Re: [Haskell-cafe] [GSoC] Porting HaRe to use the GHC API

2008-03-30 Thread Bryan O'Sullivan
Chaddaï Fouché wrote:

> My proposal for the SoC is to port HaRe (its parsing and refactoring)
> to use the GHC API instead of Programmatica.

This is an appealing idea, and it has the kind of tight scope that makes
it plausible as a summer project.  Excellent!

http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskell job opening

2008-03-30 Thread Chris Smith
MindIQ Corporation is looking for a Haskell programmer.  Details can be 
found at http://cdsmith.twu.net/jobposting.html.  This isn't "officially" 
announced yet, but it will be in a few days.

>From the announcement: Why You Want This Job

* You can program in Haskell and get a salary for it.
* Work from home. Choose your hours. Travel only if you want to.
* Build a new software application from scratch.
* Chance to work some (but not entirely) on open source stuff.
* Small company, no bureaucracy, but quite stable (around since 1986).
* You will be "Lead Software Developer" within a very short time.

Hope this is of interest.

-- 
Chris Smith
Lead Software Developer, MindIQ Corporation

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


Re: [Haskell-cafe] Re: SoC project: Python-Haskell bridge - request for feedback

2008-03-30 Thread gwern0
On 2008.03.27 14:07:23 -0700, Dan Weston <[EMAIL PROTECTED]> scribbled 0.7K 
characters:
> I did not see MissingPy on Hackage (presumably it would be next to
> MissingH?)

Remember, Hackage is alphabetical by category and then by title; I personally 
would not stick MissingH in the Unclassified category but something like 
Development.

Anyway, I doubt you'll see MissingPy on Hackage soon; note that the 
installation procedure requires you to use a python script to generate an 
appropriate cabal file. (It doesn't build for me anyway, but that's a separate 
issue.)

> I found it (listed on http://www.complete.org/jgoerzen/softindex.html) at
> http://darcs.complete.org/missingpy
>
> Is this the right place to get it?
>
> Dan

I think so. That's the host I recognize from HSH, at least.

--
gwern
Brown virtual DDR&E B83 Kwajalein Team IMF CANSLO Watergate MOD


pgpD6EyGSgW1h.pgp
Description: PGP signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Possible to automatically determine typeclass membership?

2008-03-30 Thread jeff p
Hello,

> Is it possible in Haskell + GHC extensions to use reflection
>  techniques to determine typeclass membership?  I'm thinking of things
>  like the following:
>
I think the short answer is not in general; i.e. I don't think there is any
way to access the members of an arbitrary typeclass (but I'd love to be
proved wrong).

However, you could always explicitly list the members of a typeclass you are
interested in (this is similar to your Idea 2):

{-# OPTIONS_GHC -fglasgow-exts -fallow-undecidable-instances
-fallow-overlapping-instances #-}

class InEq a b | a -> b where inEq :: a -> Bool
instance TypeCast b HFalse => InEq a b where inEq _ = False
instance InEq Int HTrue where inEq _ = True
instance InEq a b => InEq [a] b where inEq _ = inEq (undefined :: a)

data HTrue
data HFalse

class TypeCast   a b   | a -> b, b-> a   where typeCast   :: a -> b
class TypeCast'  t a b | t a -> b, t b -> a where typeCast'  :: t -> a -> b
class TypeCast'' t a b | t a -> b, t b -> a where typeCast'' :: t -> a -> b
instance TypeCast'  () a b => TypeCast a b where typeCast x = typeCast' () x
instance TypeCast'' t a b => TypeCast' t a b where typeCast' = typeCast''
instance TypeCast'' () a a where typeCast'' _ x  = x

You can also do an arguably nicer, more flexible version of the previous by
recreating some of the typeclass machinery yourself; Oleg has several
examples of this such as: //okmij.org/ftp/Haskell/poly2.txt

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


Re: [Haskell-cafe] Wumpus World

2008-03-30 Thread Benjamin L. Russell

--- "Richard A. O'Keefe" <[EMAIL PROTECTED]> wrote:

> [snip]
> 
> Let me contrast SICStus Prolog with GHC.
> I *have* a personal copy of SICStus on my SunBlade
> 100/Solaris 2.10
> system which installed absolutely trouble free.
> I *did* have a copy of GHC, but trying to install
> GHC 6.4 took
> a great deal of my time and now I don't have a
> working GHC any more.
> So for me, GHC is by far the more expensive: I've
> spent considerably
> more than 500 Euros of my time and got nothing for
> it.  Much though
> I admire Jan, I've also had such a lot of trouble
> installing SWI Prolog
> on various machines that SICStus was *really*
> cheaper than the "free"
> Prolog after all.  I do wish people would remember
> that not all the
> world is Linux.

Sorry to hear about your troubles with GHC.  Have you
tried documenting your problems and sending an inquiry
to the Glasgow-haskell-bugs mailing list (see
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs)?
 That mailing list is dedicated to GHC-related bugs,
and they tend to be quite responsive.

FWIW, I have GHC 6.8.2, which installed trouble-free,
running on a Windows XP (Service Pack 2) system at
work.  I did customize it (after installation) to
restore the original banner, but that was a
customization, not a bug-fix, and I haven't
encountered any bugs per se with it so far.

> 
> 153 Euros (why did the Europeans name their currency
> after the
> Common Wallaroo?) is NZD 303 or about the price of
> two textbooks.
> (Three copies of Bird's introduction to functional
> programming
> would do it, if they shipped free.)
> 
> You're telling me that *researchers* can't afford
> the price of
> a couple of books?

It's more than that, actually, because, in my case, I
also want to study it at home on a PPC-based PowerBook
running Mac OS X 10.2.8 Jaguar, soon-to-be-upgraded to
the PPC version of Mac OS X 10.5.x Leopard,
soon-to-be-replaced by an Intel-based MacBook Pro
running the Intel version of Mac OS X 10.5.x Leopard. 
And this is alongside studying it at work.

Granted, SICStus Prolog does appear to be an extremely
easy-to-install, fast, well-documented, stable,
industrial-grade version of Prolog.  It would probably
provide an extremely pleasant and rewarding Prolog
experience.  It is probably well-supported as well.

However, the Personal License of SICStus Prolog is
only valid for a single computer running a single copy
at any one time.  So I would actually need to purchase
a minimum of two licenses if I used it at both work
and home and then went through the trouble of
uninstalling each version of SICStus Prolog every time
I upgraded my OS at home (which I usually don't do,
because it costs already purchased time), and a
maximum of four licenses if I chose not to uninstall.

Now,

4 * 153 euros = 612 euros

which is much more than the price of a couple books.

> 
> The academic licence isn't that unreasonable.  1560
> Euros is
> NZD 3091, which is about one month of a TA's pay. 
> Another 880
> Euros gives you the right to give your students free
> binaries,
> however many students you have, year after year
> after year.
> 
> >  Can you recommend an alternative, fast
> > Prolog development system under a free licensing
> > agreement, such as GPL/GLPL?
> 
> There is, after all, GNU Prolog.  The last time I
> saw any benchmarks,
> it was substantially faster than SWI, while not
> quite as good as  
> SICStus.
> 
> See http://gprolog.inria.fr/ or
> http://www.gprolog.org/

Yes, GNU Prolog does seem one alternative.  Thank you
for providing the link.  I'll have to compare and
contrast it with SICStus Prolog and SWI-Prolog.

Although the ease of installation of SICStus Prolog
does seem enticing, the need to purchase a new license
every time I use a different computer seems a little
frightening.  What happens if one day, my boss
suddenly tells me I'm fired and prohibits access to my
work PC for "security" reasons, thereby preventing me
from uninstalling SICStus Prolog at work, and I then
need to continue studying it on a different PC at a
new job?  Wouldn't I need to purchase another Personal
License, at another 153 euros?  There is no such thing
as real job "security" in the current job market. 
This could happen without warning at any time, for any
reason or even lack of reason.

> 
> For what it's worth, GNU Prolog's developers *do*
> realise that not all
> the world's linux.

Yes, but I'm not quite sure what you mean by this,
since SWI-Prolog is also available on Windows, and I
don't use Linux, either--I use Mac OS X.  So who is it
that believes that all the world is Linux?

Benjamin L. Russell
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] lexicographic order

2008-03-30 Thread Simeon Mattes


Chaddaï Fouché-2 wrote:
> 
> 2008/3/30, Bulat Ziganshin <[EMAIL PROTECTED]>:
>>  although the last alternative,
>>(Branch l r) <= (Branch l' r')  =  l == l' && r <= r' || l <= l'
>> seems suspicious to me. isn't it the same as
>>(Branch l r) <= (Branch l' r')  =  l <= l'
> 
> Yes, it should be :
> (Branch l r) <= (Branch l' r')  =  l < l' || l == l' && r <= r'
> 
> Lexical order for a tuple (a,b) is :
> (a,b) <= (a',b') iff (a < a' or (a == a' and b <= b'))
> The same idea can be applied to list (where Nil is strictly less than
> anything else) or other datatypes.
> 
> -- 
> Jedaï
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> 



Chaddaï Fouché-2 wrote:
> 
> 2008/3/30, Bulat Ziganshin <[EMAIL PROTECTED]>:
>>  although the last alternative,
>>(Branch l r) <= (Branch l' r')  =  l == l' && r <= r' || l <= l'
>> seems suspicious to me. isn't it the same as
>>(Branch l r) <= (Branch l' r')  =  l <= l'
> 
> Yes, it should be :
> (Branch l r) <= (Branch l' r')  =  l < l' || l == l' && r <= r'
> 
> Lexical order for a tuple (a,b) is :
> (a,b) <= (a',b') iff (a < a' or (a == a' and b <= b'))
> The same idea can be applied to list (where Nil is strictly less than
> anything else) or other datatypes.
> 
> -- 
> Jedaï
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
> 
> 
Quoted from: 
http://www.nabble.com/lexicographic-order-tp16381434p16388762.html


Thanks for your help...I feel so embarrassed. With all of these symbolos in
Haskell like -> (for types), => (in classes) etc I couldn't imagine that <=
means less than or equal to!!!:clap:

>Yes, it should be :
>(Branch l r) <= (Branch l' r')  =  l < l' || l == l' && r <= r'

>Lexical order for a tuple (a,b) is :
>(a,b) <= (a',b') iff (a < a' or (a == a' and b <= b'))

I have tested it and I have found that it is the same with
(Branch l r) <= (Branch l' r')  =  (l == l' && r <= r') || l < l'

The problem with the previous is that the compiler during the parsing takes
as right
(Branch l r) <= (Branch l' r')  =  l == l' && (r <= r') || l < l')
since the infix operator && needs two operands,i.e. one on the left and the
other on the right


Though I can't understand why both
(Branch l r) <= (Branch l' r')  =  l < l' || l == l' && r <= r'
(Branch l r) <= (Branch l' r')  =  l <= l' || l == l' && r <= r'

give the same results and why I should take as right 
(a,b) <= (a',b') iff (a < a' or (a == a' and b <= b'))
and not
(a,b) <= (a',b') iff (a <= a' or (a == a' and b <= b'))

The latter seems more logical, doesn't it?


-- 
View this message in context: 
http://www.nabble.com/lexicographic-order-tp16381434p16392557.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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