[Haskell] [ANN] GenCheck - a generalized property-based testing framework

2012-06-19 Thread Jacques Carette
Test.GenCheck is a Haskell library for /generalized proposition-based 
testing/. It simultaneously generalizes *QuickCheck* and *SmallCheck*.


Its main novel features are:

 * introduces a number of /testing strategies/ and /strategy combinators/
 * introduces a variety of test execution methods
 * guarantees uniform sampling (at each rank) for the random strategy
 * guarantees both uniqueness and coverage of all structures for the
   exhaustive strategy
 * introduces an /extreme/ strategy for testing unbalanced structures
 * also introduces a /uniform/ strategy which does uniform sampling
   along an enumeration
 * allows different strategies to be mixed; for example one can
   exhaustively test all binary trees up to a certain size, filled with
   random integers.
 * complete separation between properties, generators, testing
   strategies and test execution methods

The package is based on a lot of previous research in combinatorics 
(combinatorial enumeration of structures and the theory of Species), as 
well as a number of established concepts in testing (from a software 
engineering perspective). In other words, further to the features 
already implemented in this first release, the package contains an 
extensible, general framework for generators, test case generation and 
management. It can also be very easily generalized to cover many more 
combinatorial structures unavailable as Haskell types.


The package also provides interfaces for different levels of usage. In 
other words, there is a 'simple' interface for dealing with 
straightforward testing, a 'medium' interface for those who want to 
explore different testing strategies, and an 'advanced' interface for 
access to the full power of GenCheck.


See http://hackage.haskell.org/package/gencheck for further details.

In the source repository (https://github.com/JacquesCarette/GenCheck), 
the file tutorial/reverse/TestReverseList.lhs shows the simplest kinds 
of tests (standard and deep for structures, or base for unstructured 
types) and reporting (checking, testing and full report) for the 
classical list reverse function. The files in tutorial/list_zipper show 
what can be done with the medium level interface (this tutorial is 
currently incomplete). The brave user can read the source code of the 
package for the advanced usage -- but we'll write a tutorial for this 
too, later.


User beware: this is gencheck-0.1, there are still a few rough edges.  
We plan to add a Template Haskell feature to this which should make 
deriving enumerators automatic for version 0.2.


Jacques and Gordon

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


RE: Random Permutations

2003-03-07 Thread Jacques Carette
Pertinent to this thread (though perhaps overkill) is the work of Flajolet
et al on (fast) random generation of combinatorial structures for any
structure given as a context-free grammar, including Permutation.

In particular see
http://citeseer.nj.nec.com/flajolet93calculus.html
http://citeseer.nj.nec.com/flajolet95computer.html

There is a complete implementation of this in Maple as well as a partial
port to MuPAD.  The Maple version is available at
http://pauillac.inria.fr/algo/libraries/libraries.html.  Also worth a look
is the set of fully documented example applications (available in various
formats) at
http://pauillac.inria.fr/algo/libraries/autocomb/autocomb.html

A translation of the random generation parts of this work to Haskell would
not be too difficult, and might in fact be easier than the original,
although a full translation would require Template Haskell.  Translating the
automatic generation of the 'counting' functions would be very challenging
[as no one has, as far as I know, yet to create a workable, truly
statically-typed computer algebra system!]

Jacques

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: Enum on Float/Double

2003-10-21 Thread Jacques Carette
The C function you are looking for is called 'nextafter', and is present on
all systems/libraries that pretend to be fully IEEE-754 compliant (as this
is a required function from the standard).  It even takes a direction
parameter (so you can do both nextafter and firstbefore).  Since its API is
simple, an FFI should be rather straightforward.

Jacques

-Original Message-
From: [EMAIL PROTECTED] [mailto:[EMAIL PROTECTED] On
Behalf Of Hal Daume III
Sent: October 21, 2003 2:37 PM
To: Ketil Z Malde
Cc: [EMAIL PROTECTED]; Simon Peyton-Jones; George Russell
Subject: Re: Enum on Float/Double


> > My preference would be for succ (+-0) to return the smallest 
> > positive real, since then you could define succ x to be the unique y 
> > with x < y and forall z . z < y => not (x < z), where such a y 
> > exists, and I'm not sure if the Haskell standard knows about signed 
> > zeros.
> 
> Is this really useful?  Why would you need this number?  Peano 
> artithmetic on reals? :-)

Is there any way to do this (yet)?  I found a case where I really need:
  f :: Float -> Float
where
  f x is the least y such that x < y

even if i have to FFI to C, I'd really like a solution.

any help would be appreciated.

 - Hal


___
Haskell mailing list
[EMAIL PROTECTED] http://www.haskell.org/mailman/listinfo/haskell

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] Java class file reader

2004-07-14 Thread Jacques Carette
Does anyone have a Java class file reader (written in Haskell, naturally)?
I have found a writer, but no reader?  [Google came up empty...]

If this does not exist (yet), any recommendations as to how one goes about
reading such mixed binary data?

Thanks for any help,
Jacques

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] 2-D Plots, graphical representation of massive data

2004-08-26 Thread Jacques Carette
John Meacham <[EMAIL PROTECTED]> wrote:
What would be cooler (IMHO) would be brining all of matlabs
functionality into haskell via haskell libraries so one may use 'ghci'
sort of as one uses matlab, but with the advantages haskell brings.
One could create Haskell libraries that are matlab-like, but most of the advantages of haskell (ie stong typing) are 
not realizable in Haskell.  To express even the most basic of matrix datatypes and operations requires dependent 
types.

Now, most of the dependent types needed are (linear) integer dependencies, so some of the tricks recently shown on 
this mailing list could be used, but the end result would be hardly palatable, and certainly not competitive with 
Matlab on usability grounds.

Shapely types (a la FISh) are quite promising in this direction, as are systems (like Epigram) taking dependent types 
head-on.  It is too bad that Aldor (www.aldor.org) was too far ahead of its time with its first-class and dependent 
type system :-(  Scarily, it is essentially deemed a 'failure' in Computer Algebra circles, as its type system, 
powerful as it is, is still too weak to conveniently express the mathematics of calculus.  And calculus/analysis is 
what most people use Matlab, Maple and Mathematica for.

[I was with Maplesoft Inc (makers of the CAS Maple) for 10 years, Senior Architect and Product Development Director 
for 2000-2002 before I got lured by academia.  I say this mostly as a way to allow others to judge the weight they 
should place on my above stated opinions.]

Jacques
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: [Haskell] Dependent types, was:2-D Plots, graphical representation of massive data

2004-08-27 Thread Jacques Carette
> I think Jacques possibly means the ability to do static checking of matrix
> and vector extents, to make sure that you don't try to perform operations
> like matrix-vector multiply on operands whose extents do not match. If you
> want to have this ability on your language, then you will have to restrict
> the way you are allowed to construct array bounds so the equations that
> arise can be solved. Possibly a dependent type system can be helpful for
> this.

This is indeed what I meant.

If one is going to move from a dynamically typed language (like Matlab,
Maple, Mathematica, etc) to something statically typed, then the expectation
is that this is going to truly help.  And, for many applications, it does
[this is partly why I have an MSc student coding a reverse engineering
application in Haskell].

Since the claim of static typing is that things cannot go wrong at run-time,
one start to think (incorrectly, but optimistically) that this means that
'nonsense' cannot happen at run-time.  And multiplying matricies with
non-matching sizes is nonsense, so it is rather disappointing that, without
tricks, this is not caught at compilation time.

Matrix length are one of many commonly occuring dependent types in
mathematics.  Variable names for polynomials, expansion point and 'scale'
for generalized series expansions, coefficient ring for normalization and
factorization of polynomials, and so on up the food chain.  The dependencies
get quite interesting when one is dealing with modelling mixed PDEs and
recurrence equations as ideals in rings of Ore polynomials!  

Jacques

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: [Haskell] 2-D Plots, graphical representation of massive data

2004-08-27 Thread Jacques Carette
I said:
> One could create Haskell libraries that are matlab-like, but most of
> the advantages of haskell (ie stong typing) are not realizable in 
> Haskell.  To express even the most basic of matrix datatypes and 
> operations requires dependent types.

Jerzy Karcmarczuk replied:
> I did not understand what is not realizable where...

Note that I did not say "not realizable" [this would be false], I only
claimed that most of the advantages of Haskell would be "lost".  It has been
shown how to embed a dynamically typed language into a statically typed one.
An interesting embedding of Matlab-like functionality in Haskell would
really need to feel more like Haskell than Matlab!

This is not to say that embedding Matlab functionality into Haskell, even at
the cost of having that subset be dynamically typed, would not be quite
useful.  Quite the contrary.

> I have the impression that the true calculus/math analysis percentage in 
> Matlab programs
> is negligible. Look at the composition of Matlab toolboxes. 

[This information is straight from Cleve Moler].  The main uses of Matlab
are in industry, not academia.  And there, they use toolboxes, few use 'raw'
Matlab.  The most propular toolbox is Simulink.  And the mathematics of
Simulink is partly about matricies, but mostly it is about differential
equations.  The interface just hides them from the user quite successfully.

> With symbolic packages, such
> as Maple or Mathematica it is a bit different, but statistically what 
> counts is pure algebra +
> a good deal of visualization facilities. Actually, with the development 
> of the Automatic
> differentiation techniques, one needs much less of symbolic processing 
> nowadays...

I do not understand this 'statistically what counts is pure algebra +
visualization' statement.   That visualization is extremely important I
fully agree with.  That the nitty-gritty of these systems is all implemented
using pure algebra, again agreed.  But my experience is that what most users
want is to solve differential equations (or computing quadratures, but that
is clearly the same thing).  Of course, what they really want is to not see
those DEs at all, but see control systems, circuits, chemical flows, etc.
All of which boil down to DEs.

Jacques

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: [Haskell] is $ a no-op?

2004-10-13 Thread Jacques Carette
> -- |Apply list of functions to some value, returning list of results.
> --  It's kind of like an converse map.
> flist :: [a->b] -> a -> [b]
> flist fs a = map ($ a) fs

I have attempted, unsuccessfully, to write flist above in a point-free
manner.  Is it possible?

Jacques

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


RE: [Haskell] is $ a no-op?

2004-10-13 Thread Jacques Carette
> > --  It's kind of like an converse map.
> 
> I have attempted, unsuccessfully, to write flist above in a point-free 
> manner.  Is it possible?

> Of course it is, but why?
> flist = flip (map . flip ($))

Some functions are simpler point-free, others are simpler with points.  I
was curious about this one (I like the pointwise version better).

Also, the statement "It's kind of like a converse map" becomes quite clear
from the point-free way to write it, while still not so obvious in the
pointwise version.

Jacques

___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Re: [Haskell-cafe] field record update syntax

2005-01-28 Thread Jacques Carette
"S. Alexander Jacobson" <[EMAIL PROTECTED]> wrote:
(Moved to Haskell list because this is now a suggestion for the language)
I do a lot of this soft of thing.
   foo {bar = fn $ bar foo
   ,baz = fn2 $ baz foo
   }
It would be much nicer if this syntax did the equivalent:
   foo {bar \= fn
   ,baz \= fn2
   }
-Alex-
What about 'lifting' this higher?  You are (essentially) suggesting a nice syntax for constructing functions from a 
record to itself.  While your syntax is essentially pointfree, the semantics is 'pointwise' (in that it refers to a 
specific record) -- not to be confused with the fact that any such function needs to be done compontent-wise.

Wouldn't be even more convenient (as well as more 'functional') if a syntax like
   \foo {bar \= fn
,baz \= fn2
}
built a record-to-record function?  [The \foo might even be enough to allow bar 
= fn instead of bar = fn].
Jacques
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] Typing in haskell and mathematics

2005-01-28 Thread Jacques Carette
The previous post on record syntax reminded me of some 'problems' I had noticed where Haskell and mathematics have a 
(deep) usage mismatch.

First, consider a syntax for other component-wise function application?  For example, it would be convenient to have 
(f,g) @ (x,y)
be (f x, g y).  In some languages [with dynamic typing], one can even do (f,g) (x,y) :-)  

Yes, I am aware that this untypeable in Haskell, because polymorphism is straight-jacketed by structural rules.  But 
in mathematics, it is convenient and extremely common to:
1) look at the type a -> b as being a *subtype* of b (though I have never seen it phrased that way in print)
2) to consider every 'natural transformation' available and use it (tuples of functions <-> obvious function on 
tuples)

Seeing a -> b as a subtype of b allows one to take any function f : b -> b -> c (like + ) and 'lift' it to 
ff : (a -> b) -> (a -> b) -> (a -> c)
via the obvious definition
ff g h = \x -> f (g x) (h x)
This is done routinely in mathematics.  The meaning of the expression (sin + cos) should be immediately obvious.  Such 
'lifting' is used even in first-year calculus courses, but not in Haskell.

The "same" phenomenon is what allows one to 'see' that there is an obvious 
function
apply_tuple:: (a->b,c->d) -> (a,c) -> (b,d)
so that
(f,g) (a,b)
only has one possible meaning, if the built-in apply function were to be 
overloaded.
Similarly, there are "obvious" maps
apply_T :: T (a->b) -> a -> T b
for any datatype constructor T (as has been noticed by all who do 'generic' 
programming).  This means that
[f, g, h] x == [f x, g x, h x]
but also (in mathematics at least)
{f, g, h} x == {f x, g x, h x}
where {} denotes a set, and the equality above is extensional equality, and so 
on.
Note that some computer algebra systems use #1 and #2 above all the time to define the operational meaning of a lot of 
syntactic constructs [where I personally extended the use of such rules in the implementation & operational semantics 
of Maple].  What hope is there to be able to do something 'similar' in a Haskell-like language?

Jacques
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Typing in haskell and mathematics

2005-01-28 Thread Jacques Carette
Tomasz Zielonka <[EMAIL PROTECTED]> wrote:
It's not as bad as you think. You can do this:
{-# OPTIONS -fglasgow-exts #-}
module Apply where
class Apply f a b | f -> a, f -> b where
apply :: f -> a -> b
instance Apply (a -> b) a b where
apply f a = f a
instance Apply (a1 -> b1, a2 -> b2) (a1, a2) (b1, b2) where
apply (f1, f2) (a1, a2) = (f1 a1, f2 a2)
[snip]
Very nice.  But in the scrap-your-boilerplate spirit, it would be nice if one 
could instead say
instance* Apply (T (a -> b)) a b where
apply (T f) a = T (f a)
where instance* is an instance template, and T is a ``shape functor'' (in the sense of polynomial functors specifying 
an y of algebra/coalgebra/bialgebra/dialgebra).  Or maybe even go for analytic functors (a la Joyal).

Well, I guess it's up to me to work out the theory... [based on the work of (at least) Jay, Hinze, Jeuring, Laemmel, 
Jansson and Peyton-Jones ! ]

Jacques
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


RE: [Haskell] Re: Type of y f = f . f

2005-03-01 Thread Jacques Carette
It is really too bad the 'middle' version does not work, ie

John Fairbarn's version

> d1 :: (forall c . b c -> c) -> b (b a) -> a
> d1 f = f . f

John Meacham's version (dual (?))

> d2 :: (forall c . c -> b c) -> a -> b (b a)
> d2 f = f . f

Or something in the middle

> d3 :: forall e a b . (forall c . e c -> b c) -> (e a) -> (b a)
> d3 f = f . f 

but ghci -fglasgow-exts does not like it :-(

Jacques

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


Re: [Haskell] MonadPlus

2005-04-30 Thread Jacques Carette
Ashley Yakeley <[EMAIL PROTECTED]> wrote:
I've added a bit more to .
I highly recommend people read it before they start claiming in papers 
that such-and-such a type "may thus be an instance of MonadPlus".
Very nice.
One of the problems I have encountered with MonadPlus is that too many people try to force it to be a Monoid, when it 
doesn't always want to be.  Your suggestion of separating out the identity operation from the binary operation makes 
it much clearer that these various Monads are actually instances of Magma(s)
http://en.wikipedia.org/wiki/Magma_%28algebra%29
than necessarily a Monoid.  On the above Wikipedia article, there is a useful ontology of identities that can be 
useful to describe various Magmas.

Jacques
PS: your discussion of the laws of MonadPlus reinforces to me the real need for being able to declare the laws that a 
typeclass should satisfy, not just the signature.
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] MonadPlus

2005-04-30 Thread Jacques Carette
Jan-Willem Maessen <[EMAIL PROTECTED]> wrote:
> ...discussion of the laws of MonadPlus reinforces to me the real 
> need for being able to declare the laws that a typeclass should 
> satisfy, not just the signature.

On this I cannot but agree.  But we don't usually count on being able to prove these by construction.
Note that I was just suggesting that the laws be given and available (ie as 
type-level constructs, not comments).
I was not suggesting that 'proofs' be either done by the compiler, nor even given as necessary annotations.  Although 
if they were present (as annotations), the proof itself might furnish some additional ingredients that an advanced 
optimizer might be able to use to good effect...

Jacques
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Re: Proposal: Relative Module Imports

2005-05-04 Thread Jacques Carette
Samuel Bronson <[EMAIL PROTECTED]> wrote:
On 5/3/05, S. Alexander Jacobson  alexjacobson.com> wrote:
> Problem: We need a way to simplify module imports.
> Idea: Allow module relative imports in a manner that does not break
> any existing code.
I almost want "import Text.HaXML.XML.{Types,Escape,Pretty}", but not
quite. And that would not be nice for qualified imports, anyway.
Maybe something like
from Text.HaXML.XML import (Types, Escape, Pretty)
would be nice.
That's really funny.  Some 4th year students here just finished a project under my supervision that I called 'SJ' for 
'Short Java', where the basic premise was that most Java code is unecessarily verbose.  One of the 'low hanging fruit' 
for shortening were import declarations.  I had advised the students to go with something that would be the equivalent 
of
import Text.HaXML.XML.{Types|Escape|Pretty}
but they chose something a bit worse than that.

Of course, the project aimed for more substantial 'shortenings', but the end-result was very unsatisfying as this 
particular group didn't "get it".  I will try again next year, hopefully with a bigger group.

Jacques
PS: I tried to get them to use Parsec and write their own pretty-printer for in Haskell, but gave up on that because 
of the weakness of the group.  They ended up using ANTLR (good) and some awful Java pretty-printer that was quite 
buggy :-(
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Literal for Infinity

2005-09-29 Thread Jacques Carette
The IEEE 754 standard says (fairly clearly) that +1.0 / +0.0 is one of 
the most 'stable'  definitions  of Infinity (in  Float at least).  
Throwing an exception is also regarded as a possibility in IEEE 754, but 
it is expected that that is not the default, as experience shows that 
that is a sub-optimal default.  Mathematical software (Maple, 
Mathematica, Matlab) have generally moved in that direction.


Almost all hardware implementations of float arithmetic now default to 
IEEE 754 arithmetic.  Having the arithmetic do 'something else' involves 
more CPU cycles, so users should generally complain if their system's 
arithmetic differs from IEEE 754 arithmetic without some deep reason to 
do so [there are some; read and understand William Kahan's papers for 
these].


Jacques

Yitzchak Gale wrote:


While checking for floating-point overflow and
underflow conditions, I tried to create a somewhat
reliable cross-platform Infinity with the literal
"1e10".

When GHC 6.4.1 reads this literal, it goes into a
deep trance and consumes huge amounts of
memory. Shouldn't it immediately recognize such a
thing as Infinity?

Is there a better way to check for Infinity?  I
have not yet figured out how to check for NaN at
all - because it is not equal to itself. Any
suggestions?

BTW, I notice that Simon PJ proposed literals
for Infinity and Nan several years ago:

http://www.haskell.org/pipermail/haskell/2001-August/007753.html

Did anything ever come out of this?

Regards,
Yitzchak
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell
 



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


Re: [Haskell] PROPOSAL: class aliases

2005-10-13 Thread Jacques Carette


Paul Govereau wrote:


Of course, if we
allow union and subtraction, then why not addition, intersection,
complement (ok, maybe not complement).
 

Class definitions (including constraints and defaults) are essentially 
(syntactic) theory signatures (as in Institutions, from Goguen, 
Burstall, and later many others).  And, as Oleg has pointed out some 
months back, Haskell's classes have a close relationship to Ocaml's 
Functor and Modules.  Learning from what they have learned:


1) theory signatures form a category, and have 'natural' operations 
defined on them.  Addition, intersection, union, subtraction are amongst 
them, as is renaming.  They are all very useful operations on 
specifications, so they ought to be available on class definitions as well.


2) A recent proposal to extend the language of Modules, co-authored by a 
certain Paul Goverau

(see http://www.eecs.harvard.edu/~nr/pubs/els-abstract.html)
advocates something quite similar for ML!

I firmly believe that there is a translation of all of the proposals in 
the above (via Oleg's work) into equivalent proposals for Haskell.  
Which I would certainly like to see happen.


I would recommend making sure that all the transformations available in 
Specware (http://www.specware.org/) be reviewed as well.  They overlap  
A LOT with the ones in (2) above, but I do not think the coverage is 
complete.


Jacques
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Design guidance sought for Ranged Sets

2005-12-21 Thread Jacques Carette
If you decide to continue working with infinite sets, then my advice 
would be to change your representation.  For infinite sets, do not use 
an implicit representation (ie like a potentially infinite list) but 
switch to an explicit symbolic-generator representation.  In other 
words, you need to use finite introspection to be able to do your 
computations.  So you'd have something like

RangeGen (Even "n") (BoundaryBelow "n") (BoundaryBelow $ Succ "n")
RangeGen (Odd "n") (BoundaryBelow "n") (BoundaryBelow $ Succ "n")
Then you can have rules on predicates such that
Union (Even x) (Odd y) | x == y
gives you the predicate True.

For example, this is one of the ``trick'' that Yampa uses for 
optimization, see the first paper on 
http://www.cs.nott.ac.uk/~nhn/papers.html.  See also the paper on 
Automatic Differentiation on the same page for another look at the same 
idea. 


Another way to achieve similar results is via type class encodings, see
http://www.haskell.org/pipermail/haskell/2004-November/014939.html

All of the above have one point in common: instead of encoding a lot of 
information in *functions*, you encode the information in *data*, 
whether it is normal constructors, GADTs or type classes.  Because the 
information is visible, you can inspect it in finite time.  The hard 
design decision is then, what information do you encode visibly?


The upside is that you get to inspect all the information you need to 
make good decisions (in finite time).  The downside is that you lose 
alpha-equivalence, and you must implement it yourself.  [This is a 
non-trivial downside in a functional language!].


It is perhaps worthwhile noting that Computer Algebra abounds with such 
design decisions and encoding ``tricks'' of using data instead of 
functions (which is where I first learned of this, before I recognized 
the same ideas in functional programming, as cited above).


Jacques

Paul Johnson wrote:

When I started the Ranged Sets library "infinite" sets (i.e. sets 
based on infinite lists of ranges) looked easy.  The set primitives of 
union and intersection are simple merge algorithms, so they would work 
fine on infinite lists of ranges.  Set difference is implemented as a 
combination of intersection and negation, and negation is just a 
simple rearrangement of the range end points, so that works too.


However there are cases where this reasoning doesn't work.  Suppose I 
have two ranged sets based

on
  Range (BoundaryBelow n) (BoundaryBelow (n+1))

Set X contains these ranges for all even values of n>0

Set Y contains these ranges for all odd values of n>0

The union of these sets should be the single range

  Range (BoundaryBelow 1) BoundaryAboveAll

In practice however the naive merge algorithm will never terminate 
because it has to merge an
infinite number of ranges into the single range above.  A similar 
problem occurs with intersection.  The intersection of these sets 
should be empty, but again the merge algorithm will iterate forever 
looking for the first range in the set.


As a workaround in 0.0.2 I've put a counter in.  The intersection 
routine adds a null empty range after 10 empty iterations, and the 
union routine puts a break between touching ranges after 10 full 
iterations.  Hence set membership tests are guaranteed to terminate in 
the presence of infinite lists.  However the same cannot be said of 
all the functions.  Set equality in particular has to evaluate the 
entire set in order to return True (although it does terminate at the 
first counter-example).  The question of whether a particular 
expression is guaranteed to terminate is not trivial if it contains 
even one infinite list.


So my question is this: are infinite sets worth bothering about?  
Should I continue to put in fixes to ensure termination in at least 
some cases?  Or should I just declare that infinite lists of ranges 
are unsupported?


Thanks,

Paul.

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


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


[Haskell] Re: Replacing and improving pattern guards with PMC syntax

2006-10-04 Thread Jacques Carette

Claus Reinke wrote:

My own awkward-looking translations were driven by having
found two tool's in Haskell that come close to this ideal, even
if the syntax is awkward: the mapping of pattern-match failure
to "fail" in do-notation, and the use of "fail msg=mzero" in
MonadPlus. By these means, matchings (lambdas with patterns
and explicit match failure) can be represented as do-blocks:

   lhs->rhs ==> \x->do { lhs <- return x; return rhs }  (1)

and then be composed (the examples I gave moved the \s to the front 
instead and used "mplus" to compose matchings, but we could also lift 
the compositions to function-level instead), and finally "spliced" 
back (turning explicit into implicit match failure) using fromJust or 
suchlike. Adding pattern guards into this translation was 
straightforward - they simply go between the two returns.
Note that it is very much this issue of 'monadic choice' in the case of 
pattern-match failure which is dealt with (in gory, assembly-level 
categoretical terms) in the MPC2006 paper you can find at 
http://www.cas.mcmaster.ca/~kahl/PMC/ (disclaimer: I am a co-author of 
that particular paper).


An early draft of this paper relied heavily on `mplus` with an extra 
condition -- until it was realized that very few monads satisfy this!  
This is where 'function lifting' came in, where we essentially add 
enough arrows "on the left" (in a completely deterministic and typed 
manner, see the boxed-; and boxed-+ definitions) to pull failure up to 
the right type, so that failure could be dealt with at the 'right 
time'.  It is only function types that introduce complications -- all 
other types are quite straightforward to deal with.


[Deleted: Claus' derivation of a monadic lifting of pattern-match 
failure which sure looks equivalent/ very close to what was in our 
MPC2006 paper].



hey, that's great! so the lifting we are looking for is simply

   lift match = (>>= (return . match)) . return

right? wrong, unfortunately. Looking more closely at the
translation of do-notation in 3.14 of the Report, we see
that it actually creates a new function by syntactic rather
than semantic manipulation (in fact mapping the problem
of fall-through back to a multi-equation first, then to "fail"), so we 
have no hope of reproducing the nice behaviour wrt pattern-match 
failure without using the do-notation, and all the syntax noise that 
implies.
The MPC2006 paper has a section describing *which* monad that Haskell98 
"bakes in" to its syntactic-level translation.  So we agree with your 
observation that there is a whole 'design space' of what to do on match 
failure, but Haskell 98 bakes a particular choice in.  See that section 
for how other published papers "bake in" other choices, and how large 
the design space can really be [for example, using the List monad leads 
to quite interesting ideas, as does using LogicT].



I'm not sure whether Wolfram suggested only a simplication
of the specification of pattern matching or an actual reification
of the concepts of matching, composition of matching, and
splicing of matchings into multi-alternative lambdas.
Wolfram's PMC [1] is an all-out reification of the concepts of matching, 
composition, splicing, etc.  The biggest thing it doesn't handle are 
some of Barry Jay's excellent ideas on generic pattern-matching (see 
http://www-staff.it.uts.edu.au/~cbj/patterns/).  The issue, as far as I 
see it, is that although Barry's latest ideas are first-rate, they seem 
extremely difficult to 'type' [and getting PMC to 'type' was really 
non-trivial]. 



And one of the things that would make possible is to replace some 
previously built-in and non-composable notions, like pattern-match 
fall through and composition of rule alternatives, by a smaller, yet 
more expressive core. And that is always a worthwhile goal for 
language redesign, isn't it?-)

Agreed!

Jacques

[1] Proper attribution:  the PMC is Wolfram's, I just thought it was so 
cool that I insisted on 'helping' him with the type system...

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


Re: [Haskell] Generator Function for Prime Numbers

2007-03-12 Thread Jacques Carette

And yet Taral would be wrong and Dave Feustel correct:
http://mathworld.wolfram.com/Prime-GeneratingPolynomial.html

There is a polynomial (of degree 25) in 26 variables which generates 
only primes whenever it is positive.  Surprising, yes it is.  Note that 
this polynomial is actually rarely positive!


Jacques

Taral wrote:

Not bloody likely.

On 3/12/07, [EMAIL PROTECTED] <[EMAIL PROTECTED]> wrote:

I have heard that a generator function has been found that generates
prime numbers directly using only addition and subtraction. There
purportedly have been presentations of this information to selected
mathematicians who have verified that the generator function works.
But I haven't found any confirmation by googling. Has anyone got
wind of this?

Thanks,
Dave Feustel
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell





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


Re: [Haskell] Articles on the value of strong typing

2007-03-26 Thread Jacques Carette
As far as published studies, I have found many through the Psychology of 
Programming Interest Group, which has a web site

http://www.ppig.org/
and an archived mailing list
http://www.mail-archive.com/discuss%40ppig.org/
with a fairly high density of reports on (formal) empirical studies on 
related issues.  Asking the question on their mailing list is likely to 
be return quite a few references to proper studies.


Jacques
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell