Re: [Haskell-cafe] is there some book about haskell and data struct and alg?

2008-05-31 Thread Robert Dockins

[snip]
> > Without the equivalent Haskell source code, the code must be manually
> > translated from Standard ML into Haskell.  Does anybody know why the link
> > is broken, when it may be fixed, and from where the Haskell source code
> > can be currently obtained?
> >
> > Benjamin L. Russell
>
> If you are interested in the topic, you will probably want to check out
> Edison: .
>
> I believe some of the older code in there was even written by Okasaki.

Indeed, the vast majority of the code was written by Okasaki. Most of the data 
structures from his book are in Edison.

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


Re: [Haskell-cafe] Longest increasing subsequence

2008-04-10 Thread Robert Dockins
On Thursday 10 April 2008 01:20:49 pm Matt Amos wrote:
> I'm trying to break out of my imperative mind-set by learning Haskell
> in small snippets. After a few successes I've hit a bit of a
> roadblock with one of the classic dynamic programming problems, the
> longest increasing subsequence:
>
> http://en.wikipedia.org/wiki/Longest_increasing_subsequence
>
> The most efficient algorithm relies on destructive updates, so a
> simple translation doesn't seem possible. I've been trying to think of
> a way of removing the need for destructive updates while keeping the
> efficiency, but so far without much luck. Ideally, I'd like to avoid
> threading the whole thing with a state monad, since then it would
> just be an imperative algorithm in disguise.
>
> Any suggestions would be very gratefully appreciated.

Memorization is a nice way to implement dynamic programming algorithms in 
Haskell.  Basically, you arrange it so that the underlying runtime does the 
destructive updates for you.

http://www.haskell.org/haskellwiki/Memoization


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


Re: [Haskell-cafe] Re: (flawed?) benchmark : sort

2008-03-13 Thread Robert Dockins
On Thursday 13 March 2008 07:33:12 pm Aaron Denney wrote:

[snip]
> I've seen mention of difficulties with Data.Map, and edison, but not
> in enough detail to really grasp what the problems are.  Until I do, my
> natural bias (which I'm trying to resist, really) is that it's a matter
> of lazy coding, not any inherent difficulty.

For the specific case of Edison, the Haddock documentation for the following 
two modules tells the whole sordid story:

http://hackage.haskell.org/packages/archive/EdisonAPI/1.2.1/doc/html/Data-Edison.html
http://hackage.haskell.org/packages/archive/EdisonAPI/1.2.1/doc/html/Data-Edison-Coll.html

The Cliff Notes version is that Edison assumes the following things about Eq 
and Ord instances:

*  An Eq instance correctly defines an equivalence relation (but not 
necessarily structural equality); that is, we assume (==) (considered as a 
relation) is reflexive, symmetric and transitive, but allow that equivalent 
items may be distinguishable by other means.
* An Ord instance correctly defines a total order which is consistent with the 
Eq instance for that type. 

It's not explicitly stated, but Edison also assumes that the operations within 
a class are consistent, i.e., that (not (x == y)) calculates the same 
function as (x /= y), etc.  I suppose that should go in the docs too.  Edison 
makes no particular assumptions about min and max, except that they are 
consistent with the defined order.

Anyway, the end result for Edison is that some operations aren't well-defined, 
and can't be made well-defined without restrictions.  For example, consider 
the operation of folding in non-decreasing order over the elements of a 
multi-set.  If the function being folded distinguishes between two elements x 
and y, but (compare x y) = EQ, and x and y are both contained in the 
multi-set, then the result of the fold depends on internal state that is not 
supposed to be user-visible (e.g., the exact shape of a balanced tree).

Blah, blah, blah, its all in the documentation.  The point is that making 
loose assumptions about the meaning of the operations provided by Eq and Ord 
complicates things in ways that can't be made to go away.


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


Re: [Haskell-cafe] Doubting Haskell

2008-02-16 Thread Robert Dockins
I'm going to try to respond the the main practical question in this message; 
perhaps others will feel up to addressing the more philosophical aspects.

(I see now that Cale has beaten me to the punch, but I guess I'll post this 
anyways...)

> Greetings Haskellers,
[snip quite a bit of discussion]

> Great. Next, translate the bit that
> says (pseudocode):
>
>   if(attempt_file_open)
> if(attempt_file_read)
>   process
>
> That's it. No fancy, complex error messages. Just check the error
> returns and only proceed if I have something to proceed with. Like
> grown-ups do. I *will* check my error returns. I have tormented too
> many newbies to *ever* consider doing anything else. If I cannot check
> my error returns I will not write the program.

You'll find in Haskell that the normal way of handling things like I/O errors 
is to use the exception handling mechanism.  There aren't usually "error 
returns" to check.  Instead you usually place error handlers at the positions 
where you want to be notified of errors using the "catch" or "handle" 
functions.  If you want to you can convert any IO action into one with an 
error return by using the "try" function.  The Control.Exception module is 
probably the one you want to check out.

http://www.haskell.org/ghc/docs/latest/html/libraries/base/Control-Exception.html

[snip more discussion]

> If so, 
> I sincerely suggest an example or two, like the small but well formed
> programs in K&R, Stroustrup or Gosling saying things like:
>
>   if((fp = fopen(...)) != NULL)
>   {
> if(fgets(...) != NULL)
> {
>   printf(...);
> }
>
> fclose(...)
>   }

Here is a quick example I whipped up.  It includes both a pretty direct 
translation of the above code, and another version which is a little more 
idiomatic.

Rob Dockins

--- code follows 
import Control.Exception
import System.IO


main = direct_translation

direct_translation = do
  tryh <- try (openFile "test.txt" ReadMode)
  case tryh of
Left err -> print err
Right h -> do
   tryl <- try (hGetLine h)
   case tryl of
 Left err -> do print err; hClose h
 Right l -> do
 putStrLn l
 hClose h
  
the_way_I_would_do_it = handle (\err -> print err) $
  bracket (openFile "test.txt" ReadMode) hClose $ \h -> do
 l <- hGetLine h
 putStrLn l
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Collections library

2007-11-28 Thread Robert Dockins
[snip]

> I recently withdrew from this project and offered up the libs I'd been
> working on as they are for a new owner. Didn't get any takers though
> (no surprises there!). I've always found the lack of apparent interest
> in all this somewhat puzzling myself. It's not as if there's no latent 
> demand for efficient collections. (Data.Map is probably the most
> regularly whined about of all the "standard" libs.)

FWIW, I find the same phenomenon with Edison.  I get very little feedback 
about it positive or negative; I really have no idea how many people are 
using it.  I guess people are more willing to roll their own data structures 
or use the standard libs.

It might be from a desire to limit dependencies.  If that's the case, perhaps 
continuing cabal developments will change that.

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


Re: [Haskell-cafe] Efficient and type safe flag sets

2007-11-04 Thread Robert Dockins
On Sunday 04 November 2007 04:15:45 pm Henning Thielemann wrote:
> We have
>   http://www.haskell.org/haskellwiki/EnumSet_EnumMap
>
> Is there also an efficient implementation for bit sets that fit into a
> machine word? This would be useful for foreign function interfaces.

http://www.eecs.tufts.edu/~rdocki01/docs/edison/Data-Edison-Coll-EnumSet.html
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Type without a data constructor?

2007-08-06 Thread Robert Dockins
On Monday 06 August 2007 19:23, Rahul Kapoor wrote:
> Most examples for defining algebraic types include data constructors like
> so:
>
> data Tree a = Tip | Node a (Tree a) (Tree a)
>
> I by mistake defined a type which did not specify a data constructor :

In this example, you have two different uses of the lexical name 'Term', and I 
think it is confusing you.  One kind of use is as a data constructor; the 
other is as a type constructor.  I've annotated the uses below:

> data SearchCondition
> = Term Bool-- data constructor
> | SearchCondition :||: (Term Bool)-- type constructor

> data Term a = Constant a  -- defn of type constr 'Term'

> sc :: SearchCondition
> sc = Term True -- data constructor
>
> is ok, but
>
> sc :: SearchCondition
> sc = Constant True  
 
Now, here you have an expression of type 'Term Bool'.  These can only appear 
on the right-hand side of :||: .  This probably isn't what you want.  Likely 
what you actually want is:

> data SearchCondition
> = SearchTerm (Term Bool) | SearchCondition :||: (Term Bool) 

Here, both uses of 'Term' refer to the type constructor.



> is not (though this is what I intended to capture!).
>
> So the question is what are types with no constructors good for? A
> simple example would be appreciated.

There are some situations where an explicitly empty type is useful.  
Type-level programming voodoo is one.

Other times the void type is nice because it can be used as a parameter to a 
type constructor.  For example, if you use the nested datatype representation 
of de Bruijn lambda terms [1], you can use the void type to create the type 
of closed terms (terms with no free variables).  Here's the short version:

data Void
data Succ a = Zero | Incr a
data Term a = Var a | App (Term a) (Term a) | Lam (Term (Succ a))
type ClosedTerm = Term Void



[1] Richard Bird and Ross Patterson, _de Brujin Notation as a Nested 
Datatype_, Journal of Functional Programming 9(1):77-91, January 1999.


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


Re: [Haskell-cafe] Re: Can we do better than duplicate APIs?

2007-03-28 Thread Robert Dockins
On Wednesday 28 March 2007 17:08, Benjamin Franksen wrote:
> Robert Dockins wrote:
> >>> Some sort of in-langauge or extra-language support for mechanicly
> >>
> >> producing
> >>
> >>> the source files for the full API from the optimized "core" API
> >>> would be
> >>> quite welcome.
>
> Have you considered using DrIFT? IIRC it is more portable and easier to use
> than TH.

DrIFT only works on datatype declarations (AFAIK) and doesn't really cover the 
use cases in question.

[snip]

> >>> haddock comments,
> >>
> >> I thought all the documentation would be in the API classes, not in
> >> the
> >> concrete implementations.
> >
> > It is now, but I've gotten complaints about that (which are at least
> > semi-justified, I feel).  Also, the various implementations have
> > different time bounds which must documented in the individual
> > modules.
>
> Yes, I forgot about that. Hmmm.
>
> > Ideally, I'd like to have the function documentation string
> > and the time bounds on each function in each concrete
> > implementation.  I've not done this because its just too painful to
> > maintain manually.
>
> I can relate to that. The more so since establishing such time bounds with
> confidence is not trivial even if the code looks simple. BTW, code
> generation (of whatever sort) wouldn't help with that, right?

Well, I can't imagine any tool that would prove the bounds for me unless 
automatic proof techniques have improved a _lot_ in the last week or so ;-)

However, if I could record the bounds once somewhere for each implementation 
and then have them auto merged with the documentation for each function, that 
would be great.

> I wonder: would it be worthwhile to split the package into smaller parts
> that could be upgraded in a somewhat less synchronous way? (so that the
> maintenance effort can be spread over a longer period)

Perhaps, but that only amortizes the effort rather than reducing it.


[snip]

> >> As I explained to SPJ, I am less concerned with duplicated work when
> >> implementing concrete data structures, as with the fact that there
> >> is still
> >> no (compiler checkable) common interface for e.g. string-like
> >> thingies,
> >> apart from convention to use similar names for similar features.
> >
> > Fair enough.  I guess my point is that typeclasses (ad per Edison)
> > are only a partial solution to this problem, even if you can stretch
> > them sufficiently (with eg, MPTC+fundeps+whatever other extension) to
> > make them cover all your concrete implementations.
>
> Yes, and I think these problems would be worth some more research effort.

Agreed.

> Besides, I dearly hope that we can soon experiment with associated type
> synonyms...

> Cheers
> Ben


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


Re: [Haskell-cafe] Re: Can we do better than duplicate APIs? [was: Data.CompactString 0.3]

2007-03-28 Thread Robert Dockins


On Mar 28, 2007, at 2:44 PM, Benjamin Franksen wrote:


Robert Dockins wrote:
After taking a look at the Haddock docs, I was impressed by the  
amount of
repetition in the APIs. Not ony does Data.CompactString duplicate  
the

whole
Data.ByteString interface (~100 functions, adding some more for  
encoding
and decoding), the whole interface is again repeated another four  
times,

once for each supported encoding.


I'd like to mention that as maintainer of Edison, I face similar

difficulties.
The data structure interfaces have scores of functions and there  
are about

20
different concrete implementations of various sorts.  Even minor  
interface

changes require a lot of tedious editing to make sure that everything

stays

in sync.


But... you have the type of all functions nailed down in classes.  
Thus, even
if a change in the API means a lot of tedious work adapting the  
concrete

implementations, at least the compiler helps you to check that the
implementations will conform to the interface (class);


This is true.


and users have to
consult only the API docs, and not every single function in all 20
implementations. With ByteString and friends there is (yet) no common
interface laid down anywhere. All the commonality is based on  
custom and
good sense and the willingness and ability of the developers to  
make their

interfaces compatible to those of others.


One could use code
generation or macro expansion to alleviate this, but IMO the  
necessity to
use extra-language pre-processors points to a weakness in the  
language;

it
be much less complicated and more satisfying to use a language  
feature

that

avoids the repetition instead of generating code to facilitate it.


I've considered something like this for Edison.  Actually, I've  
considered
going even further and building the Edison concrete  
implementations in a

theorem prover to prove correctness and then extracting the Haskell

source.

Some sort of in-langauge or extra-language support for mechanicly

producing
the source files for the full API from the optimized "core" API  
would be

quite welcome.  Handling export lists,


How so? I thought in Edision the API is a set of type classes.  
Doesn't that

mean export lists can be empty (since instances are exported
automatically)?


No.  Edison allows you to directly import the module and bypass the  
typeclass APIs if you wish.  Also, some implementations have special  
functions that are not part of the general API, and are only  
available via the module exports.


One could make typeclasses the only way to access the main API, but I  
rather suspect there would be performance implications.  I get the  
impression that typeclass specialization is less advanced than  
intermodule inlining (could be wrong though).




haddock comments,


I thought all the documentation would be in the API classes, not in  
the

concrete implementations.


It is now, but I've gotten complaints about that (which are at least  
semi-justified, I feel).  Also, the various implementations have  
different time bounds which must documented in the individual  
modules.  Ideally, I'd like to have the function documentation string  
and the time bounds on each function in each concrete  
implementation.  I've not done this because its just too painful to  
maintain manually.




typeclass instances,
etc, are quite tedious.

I have to admit, I'm not sure what an in-language mechanism for doing
something like this would look like.  Template Haskell is an  
option, I
suppose, but its pretty hard to work with and highly non- 
portable.  It

also
wouldn't produce Haddock-consumable source files.  ML-style first  
class

modules might fit the bill, but I'm not sure anyone is seriously

interested

in bolting that onto Haskell.


As I explained to SPJ, I am less concerned with duplicated work when
implementing concrete data structures, as with the fact that there  
is still
no (compiler checkable) common interface for e.g. string-like  
thingies,

apart from convention to use similar names for similar features.



Fair enough.  I guess my point is that typeclasses (ad per Edison)  
are only a partial solution to this problem, even if you can stretch  
them sufficiently (with eg, MPTC+fundeps+whatever other extension) to  
make them cover all your concrete implementations.




Cheers
Ben



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] Can we do better than duplicate APIs? [was: Data.CompactString 0.3]

2007-03-24 Thread Robert Dockins
On Friday 23 March 2007 18:55, Benjamin Franksen wrote:
> [sorry for the somewhat longer rant, you may want to skip to the more
> technical questions at the end of the post]
>
> Twan van Laarhoven wrote:
> > I would like to announce version 0.3 of my Data.CompactString library.
> > Data.CompactString is a wrapper around Data.ByteString that represents a
> > Unicode string. This new version supports different encodings, as can be
> > seen from the data type:
> >
> > [...]
> >
> > Homepage:  http://twan.home.fmf.nl/compact-string/
> > Haddock:   http://twan.home.fmf.nl/compact-string/doc/html/
> > Source:darcs get http://twan.home.fmf.nl/repos/compact-string
>
> After taking a look at the Haddock docs, I was impressed by the amount of
> repetition in the APIs. Not ony does Data.CompactString duplicate the whole
> Data.ByteString interface (~100 functions, adding some more for encoding
> and decoding), the whole interface is again repeated another four times,
> once for each supported encoding.

I'd like to mention that as maintainer of Edison, I face similar difficulties.  
The data structure interfaces have scores of functions and there are about 20 
different concrete implementations of various sorts.  Even minor interface 
changes require a lot of tedious editing to make sure that everything stays 
in sync.

[snip]

> The problems I (for-)see are for maintenance and usability, both of which
> are of course two sides of the same coin. For the library implementer,
> maintenance will become more difficult, as ever more of such 'almost equal'
> interfaces must be maintained and kept in sync.

This is true. For the specific case of Edison, this is not too bad because all 
the implementations are currently in one package and under the control of one 
person (namely, me).  That might, however, change in the future.  Obviously, 
it is a problem _now_ for the ByteString and friends.

> One could use code 
> generation or macro expansion to alleviate this, but IMO the necessity to
> use extra-language pre-processors points to a weakness in the language; it
> be much less complicated and more satisfying to use a language feature that
> avoids the repetition instead of generating code to facilitate it.

I've considered something like this for Edison.  Actually, I've considered 
going even further and building the Edison concrete implementations in a 
theorem prover to prove correctness and then extracting the Haskell source.  
Some sort of in-langauge or extra-language support for mechanicly producing 
the source files for the full API from the optimized "core" API would be 
quite welcome.  Handling export lists, haddock comments, typeclass instances, 
etc, are quite tedious.

I have to admit, I'm not sure what an in-language mechanism for doing 
something like this would look like.  Template Haskell is an option, I 
suppose, but its pretty hard to work with and highly non-portable.  It also 
wouldn't produce Haddock-consumable source files.  ML-style first class 
modules might fit the bill, but I'm not sure anyone is seriously interested 
in bolting that onto Haskell.

[snip]

> Here are some raw ideas:
>
> One reason why I think type classes have not (yet) been used to reduce the
> amount of API repetition is that Haskell doesn't (directly) support
> abstraction over type constraints nor over the number of type parameters
> (polykinded types?). Often such 'almost equal' module APIs differ in
> exactly these aspects, i.e. one has an additional type parameter, while yet
> another one needs slightly different or additional constraints on certain
> types. Oleg K. has shown that some if these limitations can be overcome w/o
> changing or adding features to the language, however these tricks are not
> easy to learn and apply.

I mostly put these kinds of type system tricks in the same category as TH: 
hard to use and non-portable.

[snip]

> Or maybe we have come to the point where Haskell's lack of a 'real' module
> system, like e.g. in SML, actually starts to hurt? Can associated types
> come to the rescue?

I'm not familiar enough with associated types to know if they would help with 
these sorts of problems.  Can someone more knowledgable comment?

> Cheers
> Ben


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


Re: [Haskell-cafe] what I learnt from my first serious haskell programm

2007-03-19 Thread Robert Dockins


On Mar 19, 2007, at 9:56 AM, Henning Thielemann wrote:



On Mon, 19 Mar 2007, Fawzi Mohamed wrote:

A practice I've seen a lot in small- to mid-sized programs is to  
have

a Types module that contains definitions of the types used in the
program.


ok I will think about it


I'd avoid that and suggest a more decentralized design, where each  
module

contributes one main type and according functions.


I'd just like to mention that I've used the central "Types" module  
myself on occasion.  The main reason is to avoid the need for  
mutually recursive modules, and not because its a particularly nice  
design.  I try to arrange the user-visible API around some coherent  
organizing principle, such as the one Henning proposes, but that  
sometimes leads to module dependency cycles; factoring out a Types  
module is one way to break the cycles.




Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] Church Encoding Function

2007-03-10 Thread Robert Dockins
On Saturday 10 March 2007 09:43, Joachim Breitner wrote:
> Hi,
>
> some more ideas following from the last post. I noticed how the function
> Data.Maybe.maybe converts a Haskell Maybe into a Church encoded Maybe.
> Also, the if construct, interpreted as a function, converts a Bool into
> a church encoded Bool.
>
> If lists are encoded as forall b. (a -> b -> b) -> b -> b, then foldr,
> with the right order of arguments, converts a haskell [] to a Church
> encoded List.
>
> Is there a name for these functions? “Characteristic Church Encoding
> Functions” maybe? Are there more than these:

I believe these are the same as catamorphisms.

http://en.wikipedia.org/wiki/Catamorphism

Here is the paper where the term (AFAIK) was coined (although I have to admit 
to having only skimmed it):

http://citeseer.ist.psu.edu/meijer91functional.html


I'm pretty sure you can define a catamorphism for any regular algebraic data 
type.  I'm not 100% sure what the story is for non-regular (AKA nested) 
datatypes.


> Maybe -- maybe
> Bool -- ifthenelse
> List -- foldr
> (,) -- uncurry
>
> Just a short idea while waiting at the airport...
>
> Greetings,
> Joachim
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] questions about core

2007-02-12 Thread Robert Dockins


On Feb 12, 2007, at 1:31 PM, Kirsten Chevalier wrote:


On 2/11/07, Matt Roberts <[EMAIL PROTECTED]> wrote:
  - Exactly what are the operational and denotational semantics of  
core?


Since I don't think this question has been answered yet, here's a
mailing list post from  Simon PJ that probably answers it:
http://www.haskell.org/pipermail/glasgow-haskell-users/2003- 
February/004849.html


That's from 2003, but I don't think the answer has changed since then.
If you wrote down a precise operational and/or denotational semantics
for Core, you'd probably have a research paper. (Especially if you
proved that GHC actually obeys that semantics...) (Disclaimer: my name
isn't Simon.)


At the risk of sounding self-promoting, I'd like to point out that  
the research paper I recently announced defines an intermediate  
language that is similar to GHC's core in some respects (they are  
both based on System F_omega).  I give a full (call-by-name)  
operational semantics and type system for the language in my report  
[1].  You won't find any proofs in the paper, but they're on my  
medium-term agenda.  There is also source code for an interpreter/ 
bytecode-compiler/shell for this intermediate language [2].


[1] http://www.cs.tufts.edu/tr/techreps/TR-2007-2
[2] http://www.eecs.tufts.edu/~rdocki01/masters.html



Cheers,
Kirsten




Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] pythags

2007-02-12 Thread Robert Dockins


On Feb 12, 2007, at 11:02 AM, [EMAIL PROTECTED] wrote:


Hello,

the "Advanced Monads" page in the Haskell Wikibook
(http://en.wikibooks.org/wiki/Haskell/Advanced_monads) contains the  
following

example of a List Monad

pythags = do
x <- [1..]
y <- [x..]
z <- [y..]
guard (x^2 + y^2 == z^2)
return (x, y, z)

However, whenever you load that function definition into Hugs or  
GHCi, you get a

message saying that "guard" is an undefined variable.

Does anyone know why?

Thanks.

phiroc



Another note about this function -- it doesn't actually work.  It  
will forever try increasing values of z, trying to find a z such that  
z^2 = 1^2 + 1^2, and no such z exists.  The following function,  
however, does seem to correctly generate all the Pythagorean triples.



pythags = do
   z <- [1..]
   x <- [1..z]
   y <- [x..z]
   guard (x^2 + y^2 == z^2)
   return (x,y,z)






Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] pythags

2007-02-12 Thread Robert Dockins


On Feb 12, 2007, at 11:02 AM, [EMAIL PROTECTED] wrote:


Hello,

the "Advanced Monads" page in the Haskell Wikibook
(http://en.wikibooks.org/wiki/Haskell/Advanced_monads) contains the  
following

example of a List Monad

pythags = do
x <- [1..]
y <- [x..]
z <- [y..]
guard (x^2 + y^2 == z^2)
return (x, y, z)

However, whenever you load that function definition into Hugs or  
GHCi, you get a

message saying that "guard" is an undefined variable.

Does anyone know why?

Thanks.

phiroc



Add the line


import Control.Monad


to the beginning of your program.  The 'guard' function is not  
automatically in scope.





Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] factorising to prime numbers

2007-02-09 Thread Robert Dockins


On Feb 9, 2007, at 9:20 AM, Dougal Stanton wrote:


Hi folks,

I recently read in my copy of Concrete Mathematics the relationship
between prime factors powers and lcm/gcd functions. So I decided to
reimplement gcd and lcm the long way, for no other reason than because
I could.

If you look at the definition of 'powers' you'll note it's  
infinite. So

there's no easy way to take the product of this list, if I don't know
how many items to take from it.

Is there a better way to turn an integer N and a list of primes
[p1,p2,p3,...] into powers [c1,c2,c3,...] such that

N = product [p1^c1, p2^c2, p3^c3, ...]

If I'm missing something really obvious I'll be very grateful. I can't
really work out what kind of structure it should be. A map? fold?


If I've understood correctly your list 'powers' will be all zeros  
after a certain point.  Once that happens, you don't need to examine  
that part of the list anymore.  This should at least occur as soon as  
the primes become larger than your number N (and probably sooner.   
sqrt(N) maybe? I forget).  So, you should be able to only examine a  
prefix of the list 'primes'.  The definition you have looks right, in  
that it correctly generates the correct list.  If you want to test  
that its doing the right thing, you can just examine the prefix:


> test n = product (zipWith (^) (takeWhile (or you can just create the portion of the powers list you need in the  
first place:



> powersPrefix n = map (f n) (takeWhile ((remember kids, a decidable problem is a semi-decidable problem where  
we can calculate a stopping condition).




D.


-- Concrete Mathematics
-- Graham, Knuth & Patashnuk

module Concrete where

import Data.List

-- the sieve of eratosthenes is a fairly simple way
-- to create a list of prime numbers
primes =
let primes' (n:ns) = n : primes' (filter (\v -> v `mod` n /= 0)  
ns)

in primes' [2..]

-- how many of the prime p are in the unique factorisation
-- of the integer n?
f 0 _ = 0
f n p | n `mod` p == 0 = 1 + f (n `div` p) p
  | otherwise = 0

powers n = map (f n) primes

--gcd :: Integer -> Integer -> Integer
--gcd = f . map (uncurry min)

--
Dougal Stanton




Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] List operation question

2007-02-04 Thread Robert Dockins
On Sunday 04 February 2007 14:24, Nicolas Frisby wrote:
> I've always thought that when certain operations are of particular
> interest, it's time to use more appropriate data structures, right?
> Lists are great and simple and intuitive, but if you need such
> operations as shifts, something like a deque is the way to go.
>
> I'm not a data structure pro, but I'm sure someone on this list could
> post a neat example. Or you could look for work by Osaki - he seems to
> be the reference for functional data structures. "Finger trees" and
> "tries" also get a lot of attention around here.


Also, take a look at Edison.  It has a variety of sequence implementations 
with different properties.  Several of them have efficient access to both 
ends of the sequence.


http://www.eecs.tufts.edu/~rdocki01/edison.html


> Enjoy.
>
> On 2/4/07, Lennart Augustsson <[EMAIL PROTECTED]> wrote:
> > Not much better.  You could define shiftl such that is does a single
> > traversal and
> > returns both the last element and all but the last.  That will save
> > you one traversal.
> >
> > On Feb 4, 2007, at 18:44 , Eric Olander wrote:
> > > Hi,
> > >I'm still somewhat new to Haskell, so I'm wondering if there are
> > > better ways I could implement the following functions, especially
> > >
> > > shiftl:
> > > >> moves the first element to the end of the list
> > >
> > > shiftr :: [a] -> [a]
> > > shiftr [] = []
> > > shiftr (x:y) = y ++ [x]
> > >
> > > >> moves the last element to the head of the list
> > >
> > > shiftl :: [a] -> [a]
> > > shiftl [] = []
> > > shiftl x = [last x] ++ init x
> > >
> > > -Eric
> > > ___
> > > Haskell-Cafe mailing list
> > > Haskell-Cafe@haskell.org
> > > http://www.haskell.org/mailman/listinfo/haskell-cafe
> >
> > ___
> > Haskell-Cafe mailing list
> > Haskell-Cafe@haskell.org
> > http://www.haskell.org/mailman/listinfo/haskell-cafe
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Channel9 Interview: Software Composability and the Future of Languages

2007-01-30 Thread Robert Dockins
On Tuesday 30 January 2007 19:02, Bulat Ziganshin wrote:
> Hello Tim,
>
> Saturday, January 27, 2007, 10:23:31 PM, you wrote:
> >> Humm.  While I can accept that this is a valid criticism of Haskell's
> >> monadic structure for dealing with I/O, I fail to see how it could drive
> >> a decision to prefer an imperative language like C#, where every
> >> statement has this property (overspecification of evaluation order).
> >
> > True.. perhaps his objection was related to having a bulky syntax (one
>
> on *practice*, C++ compilers can reorder statements. are this true for
> Haskell compilers?

Well... I think most reordering occurs very late in the process, during 
instruction selection.  These reorderings are very fine-grained, very local 
in scope and are really only (supposed to be!) done when the reordering can 
be shown to have no affect on the outcome of the computation.  I'd be very 
surprised to see a C or C++ compiler reordering something like function 
calls.  (Although, with gcc I believe there's a flag where you can explicitly 
mark a function as being side-effect free.  I can see a compiler perhaps 
moving calls to such functions around.  But really, how's that any better 
than what we've got in Haskell?).

Caveat: I have only a passing knowledge of the black art of C/C++ compiler 
construction, so I could be wrong.


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


Re: [Haskell-cafe] Replacing [a] with (Set c a) in Monad instance.

2007-01-30 Thread Robert Dockins
On Tuesday 30 January 2007 20:06, Bryan Donlan wrote:
> Daniel McAllansmith wrote:
> > Hello.
> >
> > Given:
> >
> > newtype Dist a = D {unD :: [(a,Int)]}
> >
> > instance Monad Dist where
> >   return x = D [(x,1)]
> >   d >>= f  = D [(y,q*p) | (x,p) <- unD d, (y,q) <- unD (f x)]
> >   fail _   = D []
> >
> >
> > How would one change Dist to wrap an instance of the (Data.Edison.Set c
> > a) typeclass so that the Monad instance could be implemented in terms of
> > e.g. singleton, unionWith, empty, etc?
>
> I don't know about Data.Edison.Set, but if it's anything like
> base/Data.Set, then there's an Ord constraint on the elements, making it
> impossible to directly transform into a monad.

There are several flavors of set typeclasses in Edison.  Some have Ord 
constraints and some don't.  All of them have an Eq constraint, however, so 
the objection still applies.  Furthermore, Edison collection classes are 
organized as types of kind *, whereas monad instances require kind * -> *.

http://www.eecs.tufts.edu/~rdocki01/docs/edison/Data-Edison-Coll.html


If you instead want to replace your list with one of the Edison sequence 
implementations, that should be possible.  However, I'm not really sure that 
it's going to buy you a lot.  From a quick glance, it looks like the regular 
list type is going to be the best datastructure for the computational pattern 
of this monad, as long as your computations are sufficiently lazy.



> However, Roberto Zunino 
> came up with a clever way to bypass this problem with GADTS:
> http://article.gmane.org/gmane.comp.lang.haskell.cafe/18118
>
> You may be able to apply this to your situation, using various Edison
> collections depending on which typeclasses your monad argument implements.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Fixed-point operator (was: seq does not preclude parametricity)

2007-01-28 Thread Robert Dockins
On Sunday 28 January 2007 23:19, Matthew Brecknell wrote:
> On Wed, 24 Jan 2007 10:41:09 -0500, "Robert Dockins" wrote:
> > newtype Mu a = Roll { unroll :: Mu a -> a }
> >
> > omega :: a
> > omega = (\x -> (unroll x) x) (Roll (\x -> (unroll x) x))
> >
> > fix :: (a -> a) -> a
> > fix f = (\x -> f . (unroll x) x) (Roll (\x -> f . (unroll x) x)) omega
> >
> > ones :: [Int]
> > ones = fix (1:)
> >
> > fibs :: [Int]
> > fibs = fix (\f a b -> a : f b (a+b)) 0 1
>
> That's an interesting definition of fix that I haven't seen before,
> though I am a little puzzled by omega. Since I have an irrational fear
> of recursion, and I like to take every opportunity I get to cure it, I
> decided to take a closer look...
>
> I figure omgea is just a way to write _|_ as an anonymous lambda
> expression.

Yup.  If you type-erase it, you get the very familiar term:

(\x -> x x) (\x -> x x)

Which is the canonical non-terminating untyped lambda term.

> But that made me wonder what it's doing in the definition of 
> fix.

I like to think of fix as implementing the semantics of recursion via the 
ascending Kleene chain.  Kleene's fixpoint theorem says that:

least_fixpoint( f ) = least_upper_bound (f^i  _|_   |   i in N )

where f^i means f composed together i times.

If you run it out, you'll see that my definition of fix calculates something 
like:

(f . f . f . f  ... ) _|_

===

f (f (f (f ( ... _|_


> I can see that without it, fix would have the wrong type, since 
>
> type inference gives the x parameters the type (Mu(b->a)):
> > -- A bit like fix, except it's, erm...
> > broke :: (a -> a) -> b -> a
> > broke f = (\x -> f . unroll x x) (Roll (\x -> f . unroll x x))
>
> So omega consumes an argument that has unconstrained type, and which
> appears to be unused. It's perhaps easier to see the unused argument
>
> with fix rewritten in a more point-full style:
> > fix' f = (\x y -> f (unroll x x y)) (Roll (\x y -> f (unroll x x y)))
> > omega
>
> Performing the application, (fix' f) becomes (f(fix' f)), and so on.
>
> So, I think I follow how this fixed-point operator works, and it seems
> reasonable to use _|_ to consume an unused non-strict argument. But I
> find it mildly disturbing that this unused argument seems to appear out
> of nowhere.
>
> Then I noticed that rewriting fix without (.) seems to work just as well
> (modulo non-termination of the GHC inliner), and without the unused
>
> argument:
> > fix :: (a -> a) -> a
> > fix f = (\x -> f (unroll x x)) (Roll (\x -> f (unroll x x)))

This is another fine way to write it.

> Of course, the corollary is that I can introduce as many unused
>
> arguments as I want:
> > fix'' f = (\x -> (f.).(unroll x x)) (Roll (\x -> (f.).(unroll x x)))
> > omega omega fix''' f = (\x -> ((f.).).(unroll x x)) (Roll (\x ->
> > ((f.).).(unroll x x))) omega omega omega -- etc...
>
> This gave me a new way to approach the question of where the unused
> argument came from. Given a function (f) of appropriate type, I can
>
> write:
> > f :: a -> a
> > (f.) :: (b -> a) -> (b -> a)
> > ((f.).) :: (c -> b -> a) -> (c -> b -> a)
>
> And so on. Nothing strange here. But all of these functions can inhabit
>
> the argument type of fix, so:
> > fix :: (a -> a) -> a
> > fix f :: a
> > fix (f.) :: b -> a
> > fix ((f.).) :: c -> b -> a
>
> Those are some strange types, and I have found those unused arguments
> without reference to any particular implementation of fix. Thinking
> about it, (forall a b . b -> a) is no stranger than (forall a . a).
> Indeed, I think the only thing that can have type (forall a . a) is _|_.
> Likewise, I can't imagine anything other than the identity function
> having the type (forall a . a -> a), and it's not too hard to see where
> (fix id) would lead.
>
> So perhaps it's not the appearance of the unused argument in the above
> definition of the fixed-point operator, but the type of the fixed-point
> operator in general that is a bit strange. Certainly, I have always
> found fix to be mysterious, even though I am getting quite comfortable
> with using it.
>
> I'm wondering: Is any of this related to the preceding discussion about
> how fix affects parametricity? Can anyone recommend some
> (preferably entry-level) readings?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Channel9 Interview: Software Composability and the Future of Languages

2007-01-27 Thread Robert Dockins
On Friday 26 January 2007 22:14, Tim Newsham wrote:
> > impractical language, only useful for research. Erik Meijer at one point
> > states that programming in Haskell is too hard and compares it to
> > assembly programming!
>
> He brings up a very good point.  Using a monad lets you deal with
> side effects but also forces the programmer to specify an exact
> ordering.  This *is* a bit like making me write assembly language
>
> programming.  I have to write:
>> do {
>>x <- getSomeNum
>>y <- anotherWayToGetANum
>>return (x + y)
>> }
>
> even if the computation of x and y are completely independant of
> each other.  Yes, I can use liftM2 to hide the extra work (or
> fmap) but I had to artificially impose an order on the computation.
> I, the programmer, had to pick an order.

Humm.  While I can accept that this is a valid criticism of Haskell's monadic 
structure for dealing with I/O, I fail to see how it could drive a decision 
to prefer an imperative language like C#, where every statement has this 
property (overspecification of evaluation order).  The only mainstream-ish 
general-purpose language I know of that I know of that attempts to addresses 
this problem head-on is Fortress.  (Although, to be honest, I don't know 
enough about Fortress to know how it handles I/O to even know if it is an 
actual improvement over the situation in Haskell.)


> Ok, maybe "assembly language" is a bit extreme (I get naming, allocation
> and garbage collection!) but it is primitive and overspecifies the
> problem.
>
> Tim Newsham
> http://www.thenewsh.com/~newsham/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] IO is not a monad

2007-01-25 Thread Robert Dockins


On Jan 25, 2007, at 6:57 AM, Yitzchak Gale wrote:


Scott Turner wrote:
Paul B. Levy's studies of "call-by-push-value" model strictness/ 
laziness using

a category theoretic approach.


That sounds interesting. Do you have a reference for that?


http://www.cs.bham.ac.uk/~pbl/papers/


The first sentence of the paper "Call-by-push-value: Deomposing Call- 
By-Value and Call-By-Name" reads:


Let us consider typed call-by-value (CBV) and typed call-by-name  
(CBN), and observe
convergence at ground type only. (This restriction does not matter in  
CBV, but in CBN,

it makes the η-law for functions into an observational equivalence.)



That sounds a lot like it explicitly excludes a polymorphic "seq".   
However, I'm not very familiar with this work, so I don't know if  
that is a critical restriction, or merely incidental to the  
presentation of this paper.




Thanks,
Yitz



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] Re: seq does not preclude parametricity (Re: IO is not a monad)

2007-01-24 Thread Robert Dockins
On Wednesday 24 January 2007 20:20, Stefan Monnier wrote:
> > FYI, don't try to run this in GHC, because it gives the simplifier fits.
>
> You mean it triggers a bug in the inliner?

http://www.haskell.org/ghc/docs/latest/html/users_guide/bugs.html

Third bullet in secion 12.2.1.


I gather that GHC HQ has decided that the problem is pathological enough to 
sweep under the rug.  I can't say I blame them.  Really, the only reason to 
construct custom fixpoint combinators is to show that it can be done :-)  
Using the built-in facilities for recursion is far easier and almost 
certainly results in better code.


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


Re: seq does not preclude parametricity (Re: [Haskell-cafe] IO is not a monad)

2007-01-24 Thread Robert Dockins


On Jan 24, 2007, at 8:27 AM, Lennart Augustsson wrote:


Well, I think fix destroys parametricity too, and it would be better
to get rid of fix.  But I'm not proposing to do that for Haskell,
because I don't have a viable proposal to do so.  (But I think the
proposal would be along the same lines as the seq one; provide fix
in a type class so we can keep tabs on it.)
BTW, fix can be defined in the pure lambda calculus, just not in  
simply

typed pure lambda calculus (when not qualified by "typed" the term
"lambda calculus" usually refers to the untyped version).



I think its important to point out here that fix _can_ be defined in  
sufficiently rich typed lambda-calculi.  You just need unrestricted  
recursive types (iso-recursive is sufficient).  Since Haskell has  
those, you can't get rid of fix using typeclasses.  You would also  
need something like the strict positivity restriction, which is a  
pretty heavyweight restriction.





newtype Mu a = Roll { unroll :: Mu a -> a }

omega :: a
omega = (\x -> (unroll x) x) (Roll (\x -> (unroll x) x))

fix :: (a -> a) -> a
fix f = (\x -> f . (unroll x) x) (Roll (\x -> f . (unroll x) x)) omega

ones :: [Int]
ones = fix (1:)

fibs :: [Int]
fibs = fix (\f a b -> a : f b (a+b)) 0 1

main = print $ take 20 fibs





FYI, don't try to run this in GHC, because it gives the simplifier fits.



[snip]


Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] IO is not a monad (and seq, and in general _|_)

2007-01-23 Thread Robert Dockins

On Jan 23, 2007, at 2:09 PM, Brandon S. Allbery KF8NH wrote:

Can someone explain to me, given that (a) I'm not particularly  
expert at maths, (b) I'm not particularly expert at Haskell, and  
(c) I'm a bit fuzzybrained of late:


Given that _|_ represents in some sense any computation not  
representable in and/or not consistent with Haskell,


I'm not sure you've got quite the right notion of what bottom  
"means."  There are lots of computations that are representable in  
Haskell that are equivalent to _|_.  _|_ is just a name we give to  
the class of computations that don't act right (terminate).


why/how is reasoning about Haskell program behavior in the presence  
of _|_ *not* like reasoning about logic behavior in the presence of  
(p^~p)->q?


You seem to be talking around the edges of the Curry-Howard  
isomorphism.  C-H basically says that there is a correspondence  
between typed lambda calculi and some logical system.  Types  
correspond to logical formulas and lambda terms correspond to  
proofs.  However, a system like Haskell's (where every type is  
inhabited) corresponds to an inconsistent logic (one where every well- 
formed statement is provable).  That just means that the logic system  
corresponding to Haskell's type system isn't a very useful one.   
However, we don't reason _about_ Haskell using that logic, so its not  
really a problem.


Its possible, however, that I don't understand your question.  The  
formula (p^~p)->q (AKA, proof by contradiction) is valid most  
classical and constructive logics that I know of, so I'm not quite  
sure what you're getting at.




Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] seq (was: Article review: Category Theory)

2007-01-19 Thread Robert Dockins
On Friday 19 January 2007 18:09, Brian Hulley wrote:
> Neil Mitchell wrote:
> > Hi Brian,
> >
> >> Is there any solution that would allow excess laziness to be removed
> >> from a Haskell program such that Hask would be a category?
> >
> > class Seq a where
> >seq :: a -> b -> b
> >
> > Then you have a different seq based on the types, and it doesn't go
> > wrong. You would probably want deriving Seq support.
>
> This seems an amazingly neat solution to a really terrible problem, so:
>
> 1) Does anyone know why this was not used in the first place?

It was this way in Haskell 1.4, but was changed for Haskell 98.

IIRC, there is a fairly complete discussion of this issue in the "History of 
Haskell" paper draft that SP Jones et al circulated about for comment.  
Unfortunately, those drafts seem to have been pulled now, so I can't double 
check or give you a link.


> 2) Would it be good to use this in future versions of Haskell?
>
> 3) Is there any practical program which requires the current seq that could
> not be rewritten to use the typeclass seq?
>
> Thanks, Brian.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] STM and random numbers

2007-01-12 Thread Robert Dockins


On Jan 12, 2007, at 10:58 AM, Chad Scherrer wrote:


Hi,

I'd like to be able to use randomIO, but I'm working within the
context of STM. Is there a way to get these working together happily?

For now, I guess I could kludgingly use unsafePerformIO inside STM
(it's the other way around that's not allowed, right?), but I would
need to be sure it doesn't get inlined.


Humm... I'd actually suggest you stop trying to break the rules, and  
use the portion of the random interface that doesn't require IO.  You  
can pretty easily wrap a StdGen using StateT, and write your stuff in  
the monad (StateT StdGen STM).


Or, (and I'm amazed this hasn't been done before), you can create a  
custom random monad that wraps up this behavior.  Prototype  
attached.  Now you can write in (RandT StdGen STM), and use the  
convenient getRandom method.


Invoke like:

dostuff :: IO ()
dostuff = do
gen <- newStdGen
x <- atomically (evalRandT stuff gen)
process x

stuff :: RandT StdGen STM Int
stuff = do
 r <- getRandom
 lift (someSTMaction r)




Thanks,

Chad



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG




Random.hs
Description: Binary data


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


Re: [Haskell-cafe] Re: Versioning

2006-12-20 Thread Robert Dockins


On Dec 20, 2006, at 2:37 PM, Joachim Durchholz wrote:


Ross Paterson schrieb:
It might be not feasible though. The papers mention that you  
can't serialize (well, actually unserialize) function values with  
it. For the envisioned update-through-marshalling process, this  
would prevent me from ever using function values in data that  
needs to be persistent, and that's quite a harsh restriction.

That's hard to avoid, unless you have a data representation of the
functions you're interested in.


I could encode functions by their name. I don't think that would  
scale to a large application with multiple developers, but it's not  
this kind of project anyway.
I'd be reluctant to accept that way if it means adding boilerplate  
code for every function that might ever be serialized. Since I'm  
planning to serialize an entire application, I fear that I'd need  
that boilerplate code for 90% of all functions, so even a single  
line of boilerplate might be too much.


Let me just say here that what you are attempting to do sounds very  
difficult.  As I understand, you want to be able to serialize an  
entire application at some (predetermined / arbitrary?) point, change  
some of its code and/or data structures, de-serialize and run the  
thing afterwards.  Doing something like this without explicit  
language support is going to be hard, especially in a fairly static  
language like Haskell.


I would think Smalltalk, Erlang, or something from the Lisp/Scheme  
family would be more suitable for this sort of work (caveat, I have  
little experience with any of these languages).  Also, take a look  
here (http://lambda-the-ultimate.org/node/526) for some related  
discussion.





Regards,
Jo



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] FD problem in GHC 6.6

2006-12-20 Thread Robert Dockins


On Dec 19, 2006, at 10:11 PM, Dan Weston wrote:


> instance CommandFunction (Sh st ()) st where
   ^
I think your first argument (on which the second has a functional  
dependence) does not determine the second argument, since it makes  
use of st in the first argument. This strikes me as a likely place  
to begin.


No, I'm pretty sure this isn't a problem.  The second argument is  
determined _because_ it is mentioned in the first.  The functional  
dependencies and instance declarations work, as long as I can make  
the compiler accept them.  They are only being rejected by the  
termination-checking part of the algorithm.


That said, I'm open to the idea of reformulating these instances.  In  
fact, I don't really like the fact that I need FDs.  It seems to me  
that I should somehow be able to eliminate the second argument  
altogether and thus the FD, but I can't seem to figure it out.



Dan

Robert wrote:

Fellow Haskellers,
I have a package that uses some light typeclass hackery to  
automaticly

build parsing algorithms based on the type of a function.
I was recently informed that my package doesn't compile on GHC 6.6  
due
to the new restrictions on FD resolution; in particular I have  
instance
declarations which fail the coverage condition.  I can use  
undecidable
instances to make the package compile again, but I'd prefer not to  
if I

can avoid it.
class CommandFunction f st | f -> st where
  parseCommand  :: String -> f -> CommandParser st
  commandSyntax :: f -> [Doc]
instance CommandFunction (Sh st ()) st where





  parseCommand wbc m str =
 -- list monad
 do (x,[]) <- runRegex (maybeSpaceBefore (Epsilon  
(CompleteParse

 m))) str
return x
  commandSyntax _ = []
instance CommandFunction r st
  => CommandFunction (Int -> r) st where
  parseCommand = doParseCommand Nothing intRegex id
  commandSyntax f = text (show intRegex) : commandSyntax (f  
undefined)

instance CommandFunction r st
  => CommandFunction (Integer -> r) st where
  parseCommand = doParseCommand Nothing intRegex id
  commandSyntax f =  text (show intRegex) : commandSyntax (f  
undefined)







Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] [Haskell] Defining Cg, HLSL style vectors in Haskell

2006-11-28 Thread Robert Dockins


On Nov 28, 2006, at 7:46 AM, Slavomir Kaslev wrote:


Hello,

I have to define a couple of float2, float3, float4 Cg, HLSL style
vectors in Haskell. At first I was tempted to make them instances of
Num, Floating, RealFrac, etc. but some of the functions defined in
those classes have no sense for vectors. One such example is signum
from class Num.

There are several workarounds for this. One may come up with some
meaning for vectors of such functions, for example:

instance Num Float3 where
   .
   signum a | a == Float3 0 0 0 = 0
 | otherwise = 1

This is silly. Other option, which I prefer, is to leave such
functions undefined (that is signum=undefined, not just not defining
them). Is this ok? Are there any other options?


This will work.  So long as you don't call signum, all will be well.


Another bugging thing is that some of the functions do have meaning
for vectors but they need different signatures. For example (**) ::
Floating a => a -> a -> a, for vectors should be (**) :: (Floating a,
Vector v) => v -> a -> v, that is (**) applied for every component of
the vector. Any workarounds for that?

I know that I can scrap all those Num, Floating, RealFrac, etc.
classes and define class Vector from scratch, but I really don't want
to come up and use different names for +, -, etc. that will bloat the
code.



The inflexibility of the numeric classes is one of the well-known  
problems with the definition of the Haskell prelude.  As you say,  
there are a number of things for which only a subset of the  
operations make sense, or where more general types are needed for the  
operations.  There have been a couple of attempts to reformulate  
these classes so that they are more flexible.


Here is one that I know of:
http://darcs.haskell.org/numericprelude/

I haven't used it, so I can't really comment, other than to say it  
exists.  I seem to recall that there were several other attempts in a  
similar vein, but my brief google search didn't turn them up.  Can  
someone else fill in?



If you want to roll your own, you can still use the nice names if you  
explicitly import the prelude and hide names.  Eg,


import Prelude hiding ( (+), (-),  etc  )

Hope that helps.


Last question: Does haskell have something like C++ templates? For
example, some time in the future I may need types like int2, short3,
etc., that behave just like float2, float3, but use different types
for their components. I really, really wouldn't like to copy-paste the
definitions of floatn and manually change their types to intn
respectfully.

Cheers.

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




Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] Collection of objects?

2006-11-17 Thread Robert Dockins


On Nov 17, 2006, at 12:36 PM, Valentin Gjorgjioski wrote:

Is some kind of collection of object with different types in  
Haskell exist? Except the tuples, which have fixed length.

I find this

   * Tuples heterogeneous, lists homogeneous.
   * Tuples have a fixed length, or at least their length is  
encoded in

 their type. That is, two tuples with different lengths will have
 different types.
   * Tuples always finite.

But I need something which is heterogeneous and non-fixed length.  
I'm used do Java, and this switch to functional languages is very  
strange to me. So, to be clear, I need something like  
LinkedList in java.




The thing you're looking for doesn't really exist. (OK, yes, I'm  
lying a bit.  You can use existential types, but you probably don't  
actually need them, and they can get complicated quickly; they're  
better left until later).


Can you give us more details about what you're trying to do?  
Readjusting your thinking patterns can be difficult, but the people  
on this list are usually happy to help.




Can you please help me or suggest me, what can I use in this case?

Valentin



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] Re: Debugging partial functions by the rules

2006-11-15 Thread Robert Dockins
On Wednesday 15 November 2006 15:53, John Hughes wrote:
> > From: Robert Dockins <[EMAIL PROTECTED]>
> >
> > It seems to me that every possible use of a partial function has some
> > (possibly imagined) program invariant that prevents it from failing.
> > Otherwise it is downright wrong.  'head', 'fromJust' and friends
> > don't do anything to put that invariant in the program text.
>
> Well, not really. For example, I often write programs with command line
> arguments, that contain code of the form
>
> do ...
>[a,b] <- getArgs
>...
>
> Of course the pattern match is partial, but if it fails, then the standard
> error message is good enough.

I'd actually put this in a different category than 'partial function' (in what 
might be regarded as an abuse of termonology).  This is failure in a monad, 
and is something I personally use a lot.  Failure in IO just usually happens 
to have behavior very similar to calling 'error'.

I'll often write code in an arbitrary monad just to model partiality via 
the 'fail' function.  Sometimes, as here, I use partial pattern matches to do 
this implicitly.  Why is this better than 'error'?  Because it allows the 
code consumer decide how to deal with problems.  You can use runIdentity to 
convert 'fail' to 'error'.  You can run with runErrorT and recover the error 
message.  You can run it in a custom moand that has some other fancy error 
handling. etc, etc.


> This applies to "throw away" code, of course, and if I decide to keep the
> code then I sooner or later extend it to fix the partiality and give a more
> sensible error message. But it's still an advantage to be ABLE to write the
> more concise, but cruder version initially.

I'm not against partial pattern matching.  I think it's way better than using 
partial projection functions.

> This isn't a trivial point. We know that error handling code is a major
> part of software cost--it can even dominate the cost of the "correct case"
> code (by a large factor). Erlang's "program for the correct case" strategy,
> coupled with good fault tolerance mechanisms, is one reason for its
> commercial success--the cost of including error handling code *everywhere*
> is avoided. But this means accepting that code *may* very well fail--the
> failure is just going to be handled somewhere else.
>
> Haskell (or at least GHC) has good exception handling mechanisms too. We
> should be prepared to use them, and "let it fail" when things go wrong. The
> savings of doing so are too large to ignore.
>
> John

-- 
Rob Dockins

Talk softly and drive a Sherman tank.
Laugh hard, it's a long way to the bank.
   -- TMBG
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Debugging partial functions by the rules

2006-11-15 Thread Robert Dockins


On Nov 15, 2006, at 9:48 AM, Jón Fairbairn wrote:


Simon Peyton-Jones <[EMAIL PROTECTED]> writes:


| The problem I see is that head/fromJust errors are usually
|caused by *beginner* Haskellers, who don't know the
|techniques for statically avoiding them.

I don't agree.  My programs have invariants that I can't
always express in a way that the type system can
understand. E.g. I know that a variable is in scope, so
searching for it in an environment can't fail:
head [ v | (n,v) <- env, n==target ] (Maybe if I had
an Oleg implant I could express all this in the type system
-- but I don't.)


But instead of “blah (head [ v | (n,v) <- env, n==target ])
blah”, you could write

blah the_v_in_scope blah
where (the_v_in_scope:_) =  [ v | (n,v) <- env, n==target ]

and get a source-code located error message, couldn't you?
It's not very high tech, but it's what you would write if
head didn't exist, and it doesn't seem /that/ great an
imposition.


Or how about ??

lookupVarible target env =
   case [ v | (n,v) <- env, n==target ] of
  (x:_) -> x
  _ -> assert False $ "BUG: Unexpected variable out of scope "++ 
(show target)++" in environment "++(show env)



 ... lookupVariable target env 


It seems to me that every possible use of a partial function has some  
(possibly imagined) program invariant that prevents it from failing.   
Otherwise it is downright wrong.  'head', 'fromJust' and friends  
don't do anything to put that invariant in the program text.


Custom functions like the above 1) give you a great opportunity to  
add a meaningful assertion AND document the program invariant 2)  
attach some semantic meaning to the operation by naming it 3) make  
you think about what you're doing and help you avoid writing bugs in  
the first place 4) give you nice hooks for replacing your data- 
structure with a better one later, should it be necessary 5)  
encourage you to break down larger functions into smaller ones.


Big win if you ask me.  The frequent use of partial functions from  
the Prelude counters all of these advantages, and I avoid them as  
much as possible.




--
Jón Fairbairn  
[EMAIL PROTECTED]





Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


[Haskell-cafe] Re: Fractional/negative fixity?

2006-11-08 Thread Robert Dockins


On Nov 8, 2006, at 3:58 AM, [EMAIL PROTECTED] wrote:


Lennart Augustsson wrote:


On Nov 7, 2006, at 11:47 ,
[EMAIL PROTECTED] wrote:


Henning Thielemann wrote:

On Tue, 7 Nov 2006, Simon Marlow wrote:

I'd support fractional and negative fixity.  It's a simple  
change to

make, but we also have to adopt

[...]


I think that computable real fixity levels are useful, too. A  
further
step to complex numbers is not advised because those cannot be  
ordered.


But ordering of the computable reals is not computable.  So it could
cause the compiler to loop during parsing. :)


Actually, that's one of the use cases ;)


A turing-complete type-checker isn't enough!  Our work is not  
complete until the parser is a universal machine as well!




Regards,
apfelmus



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] List comparisons and permutation group code

2006-10-19 Thread Robert Dockins


On Oct 19, 2006, at 12:51 PM, David House wrote:


On 19/10/06, Mikael Johansson <[EMAIL PROTECTED]> wrote:

isIdentity xs = all (\(i,j) -> i==j) (zip [1..] xs)
isIdentity' xs = xs == [1..(length xs)]

Then
isIdentity 1:3:2:[4..10]
finishes in an instant, whereas
isIdentity' 1:3:2:[4..10]
takes noticable time before completing.


Why is this so? I'd have thought that the equality function for lists
only forces evaluation of as many elements from its arguments as to
determine the answer. In other words, the computation should go
something like this:


I wondered this too for a minute.  I'm pretty sure that the answer is  
that the 'length' function is the culprit, not (==).
Calling 'length' forces the spine of 'xs', which accounts for the  
extra computation.


Just say 'no' to length (when you want laziness).

[snip]



--
-David House, [EMAIL PROTECTED]



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] Error building Edison 1.2.0.1

2006-10-18 Thread Robert Dockins


On Oct 17, 2006, at 1:46 PM, Gregory Wright wrote:



On Oct 17, 2006, at 1:07 PM, Robert Dockins wrote:



On Oct 17, 2006, at 12:55 PM, Gregory Wright wrote:



Hi Rob,

I've built Edison 1.2.0.1 using ghc-6.6.  (I'm testing the macports,
formerly darwinports, packages for the new 6.6 release.)

The build goes fine, but the ./Setup register fails claiming that  
the directory
/opt/local/lib/EdisonAPI-1.2/ghc-6.6/include does not exist.  I  
can make the
directory by hand, and the registration works.  I have an ugly  
workaround,
but I wanted to check with you that this is really a cabal bug.   
Installation

using ghc-6.4.2 on OS X/ppc worked just fine for me.

Best Wishes,
Greg



I'm not doing anything unusual with the cabal scripts (that I'm  
aware of!), so I expect this is a cabal or GHC bug.


BTW, could you run the test suite if you get a moment?  Every data  
point helps.





Hi Rob,

OK, it looks like cabal has gone slightly broken again. :-(



Any idea what the problem is?  Or why other people aren't yelling  
about it?  Is it only the "register" command that is broken?




Here's the test data:

OS X 10.4.8/ppc
PowerBook G4, 1.5 GHz, 1 GB ram
	ghc-6.6, cabal 1.1.6 as distributed with ghc-6.6, built using  
macports


test output:

Welcome to Darwin!
crossroads-able> cd ~/Desktop/edison-1.2.0.1-source/test/
crossroads-able> ./dist/build/testSuite/testSuite
Cases: 1728  Tried: 1728  Errors: 0  Failures: 0
crossroads-able>



Excellent.  That's what I like to see.  Thanks!



Everything looks good but for the package registration.

I should add that I find the Edison package wonderfully easy
to work with.  It has really helped me out while writing simulation
of the custom communication system for a customer.  Many thanks
to you, Rob, and Chris Okasaki for this fine software!

Best Wishes,
Greg



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] Newbie and working with IO Int and Int

2006-10-17 Thread Robert Dockins


On Oct 17, 2006, at 1:37 PM, Víctor A. Rodríguez wrote:


What's wrong with doing it this way?

-- ** UNTESTED CODE **

verifyAdd :: Int -> Int -> Int -> Bool
verifyAdd a b sum | a + b == sum = True
otherwise = False

testAddMundane :: Int -> Int -> Bool
testAddMundane a b = verifyAdd a b (a + b)

-- all the IO-dependent stuff is below this line --

testAddRandom :: IO Bool
testAddRandom = do a <- randomIO
b <- randomIO
return verifyAdd a b (a + b)


I discovered something worst yet :-P
Using the next code and calling verifyAdd or testAddMundane it says :

Program error: verifyAdd: ERROR

Instead calling testAddRandom only says :

:: IO Bool
(55 reductions, 92 cells)


This is due to the magic of lazy evaluation.  You never use the  
result of 'testAddRandom', so it's never evaluated, which means your  
call to 'error' is also never evaluated.


Type:

testAddRandom >>= print

on the command line and you should get the same error, because the  
call to 'print' demands the result of running testAddRandom.




 CODE STARTS HERE, AND IS TESTED -

import Random

verifyAdd :: Int -> Int -> Int -> Bool
verifyAdd a b sum = error "verifyAdd: ERROR"

testAddMundane :: Int -> Int -> Bool
testAddMundane a b = verifyAdd a b (a + b)

-- all the IO-dependent stuff is below this line --

testAddRandom :: IO Bool
testAddRandom = do a <- randomIO
b <- randomIO
return ( verifyAdd a b (a+b) )

--
Víctor A. Rodríguez (http://www.bit-man.com.ar)
El bit Fantasma (Bit-Man)
Perl Mongers Capital Federal (http://cafe.pm.org/)
GNU/Linux User Group - FCEyN - UBA (http://glugcen.dc.uba.ar/)

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



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] Error building Edison 1.2.0.1

2006-10-17 Thread Robert Dockins


On Oct 17, 2006, at 12:55 PM, Gregory Wright wrote:



Hi Rob,

I've built Edison 1.2.0.1 using ghc-6.6.  (I'm testing the macports,
formerly darwinports, packages for the new 6.6 release.)

The build goes fine, but the ./Setup register fails claiming that  
the directory
/opt/local/lib/EdisonAPI-1.2/ghc-6.6/include does not exist.  I can  
make the
directory by hand, and the registration works.  I have an ugly  
workaround,
but I wanted to check with you that this is really a cabal bug.   
Installation

using ghc-6.4.2 on OS X/ppc worked just fine for me.

Best Wishes,
Greg



I'm not doing anything unusual with the cabal scripts (that I'm aware  
of!), so I expect this is a cabal or GHC bug.


BTW, could you run the test suite if you get a moment?  Every data  
point helps.




Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG


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


Re: [Haskell-cafe] Newbie and working with IO Int and Int

2006-10-17 Thread Robert Dockins


On Oct 17, 2006, at 12:21 PM, Víctor A. Rodríguez wrote:


Hi all,

I'm really newbie to Haskell, and working on a program I'm trying  
to make

some testing.
I make some test on certain know values ( e.g. adding 10 to 15 must  
return
25) and some test on random values (eg. adding rnd1 to rnd2 must  
return

rnd1+rnd2).


Probably the best way to deal with this is to use the QuickCheck  
library.

http://www.cs.chalmers.se/~rjmh/QuickCheck/

It makes this sort of thing fairly painless, because you don't have  
to muck about with generating random data manually.



The problem that makes me mad is the random number generation. I  
can obtain
random numbers through module Random but all of them return IO Int  
values

(all I need are Ints) instead of Int.
I know that I can adjust my own functions to use IO Int instead of  
Int but
the call to certain functions must contain Int parameters, because  
these

ones can't be changed to accept IO Int (I read
http://haskell.org/hawiki/ThatAnnoyingIoType and know that can  
convert from

IO Int to Int :-P).

How can I deal with this problem ??


See: http://www.haskell.org/ghc/dist/current/docs/libraries/base/ 
System-Random.html


If you use 'getStdGen' or 'newStdGen' (which are in the IO monad),  
then you can later use the pure functions 'random', 'randomR' and  
friends.  Alternately, you can manually seed the PRNG with 'mkStdGen'  
and avoid the IO monad altogether.




Thanks in advance.
--
Víctor A. Rodríguez (http://www.bit-man.com.ar)
El bit Fantasma (Bit-Man)
Perl Mongers Capital Federal (http://cafe.pm.org/)
GNU/Linux User Group - FCEyN - UBA (http://glugcen.dc.uba.ar/)



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] function result caching

2006-10-14 Thread Robert Dockins
On Saturday 14 October 2006 13:13, Ketil Malde wrote:
> Robert Dockins <[EMAIL PROTECTED]> writes:
> >>> slowFunctionCacheList= [slowFunction (i) | i <-[0..500]]
> >>> and use "slowFunctionCacheList !! i" instead of "slowFunction (i)"
> >>
> >> Not much different in principle, but better in practice - you could
> >> use an array rather than a list.  O(1) lookups should make things (a
> >> lot) faster.
> >
> > Well, this is true only if the range of the domain function is small and
> > fairly dense.
>
> I don't think so.
>
> > With 500 elements, you're looking at allocating about 20Mb of
> > memory
>
> On the other hand, the lists allocates the 20Mb of pointers, *and*
> another 20Mb of cons cells for the lists.

True, but only if you access deeply into the tail of the list.  If one access 
only the first several hundred elements, say, then you'll only allocate the 
space needed for those.

Of course, if you only want to access a small portion at the begining, then 
why create such a big list in the first place?  Moral: lists will lose this 
contest in almost all cases.

> > to hold pointers to closures_ and then allocating and filling out 500
> > closures, all before you get down to doing any real work!
>
> If I interpret you correctly, you want to make the array's contents
> strict?  Not a good idea when the domain is sparse, but on the other
> hand it would let you unbox the contents, which means you'd only need
> to store the actual values. For boolean values, I think GHC
> stores one bit per value, i.e. less than a MB for this range.

No, I didn't suggest that the elements be strict.  That would involve 
precomputing the entire table.  You _could_ do that if you anticipate a LOT 
of access to sufficient to outweigh the initial cost.  But that seems 
unlikely for a sparse domain, as you mentioned.

However, even non-strict arrays are created all at once (ie, they are strict 
in their _structure_), and the closures have to be allocated as the array is 
being created.  Creating a closure isn't terribly expensive, but creating 
500 closures might take awhile and cost a lot of memory if the closure 
has a large number of free variables (which depends on the function 
definition and the exact details of the lambda lifter).  Also, large arrays 
tend to play havoc with GHC's garbage collector; it has to scan all elements 
on every major GC, IIRC.  That alone may offset any advantages won.

In the end, the only way to be sure which method is best is to test it against 
your usage profile.  My guess is that the array method will have enough 
overhead that it will lose against a tree.  However I may be wrong, 
especially if the program will have a very long runtime and if a "warm-up" 
period is acceptable.

> > Little-endian patricia trees [...]
>
> Yes, sure, if you can't afford a 20Mb index.  On the other hand,
> changing the function to use an array is a very small modification,
> and probably more than good enough in many cases.

I completely agree; it is good for many cases, and can be a very useful 
technique.  I just don't think it will be good for _this_ case (large, sparse 
domain where f(n) doesn't depend on all f(m) where m < n).  That probability 
is positively correlated with the size of the domain.  Again, the only way to 
really know is to implement and benchmark.  Thankfully, caching techniques 
are completely local and can be changed easily.

> -k

-- 
Rob Dockins

Talk softly and drive a Sherman tank.
Laugh hard, it's a long way to the bank.
   -- TMBG
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] function result caching

2006-10-13 Thread Robert Dockins
On Friday 13 October 2006 16:15, Ketil Malde wrote:
> "Silviu Gheorghe" <[EMAIL PROTECTED]> writes:
> > slowFunctionCacheList= [slowFunction (i) | i <-[0..500]]
> > and use "slowFunctionCacheList !! i" instead of "slowFunction (i)"
> >
> > i am still curious about a better method (and a general one)
>
> Not much different in principle, but better in practice - you could
> use an array rather than a list.  O(1) lookups should make things (a
> lot) faster.

Well, this is true only if the range of the domain function is small and 
fairly dense.  He said it was large and sparsely populated.  

With 500 elements, you're looking at allocating about 20Mb of memory _just 
to hold pointers to closures_ and then allocating and filling out 500 
closures, all before you get down to doing any real work!  That's just not 
going to be very fast.  You're going to take a HUGE constant runtime and 
space penalty for that O(1) lookup.

Little-endian patricia trees are probably the right way to go here (which I 
think has been mentioned already).  You get O(log n) lookup and good behavior 
for a sparse and/or infinite domain because only the parts of the tree that 
are explored get unfolded.


> -k

-- 
Rob Dockins

Talk softly and drive a Sherman tank.
Laugh hard, it's a long way to the bank.
   -- TMBG
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [off-topic / administrative] List Reply-to

2006-10-11 Thread Robert Dockins


On Oct 11, 2006, at 11:53 AM, Udo Stenzel wrote:


Mikael Johansson wrote:

On Tue, 10 Oct 2006, Misha Aizatulin wrote:
Here is an argument against Reply-To munging. I'd say I agree  
with it:


http://www.unicom.com/pw/reply-to-harmful.html



* It provides no benefit to the user of a reasonable mailer.
[...]
1) get multiple copies of mails concerning discussions I  
participate in or
2) have to manually re-edit the header each and every time I want  
to keep
a discussion on a mailing list, possibly with added trouble  
finding the

right adress to send to


A reasonable mailer has functions "reply", "reply-to-all" and
"reply-to-list".  I'm composing this mail using "reply-to-list",  
have to

edit no headers, the reply goes to the list and nobody gets duplicate
copies.



FWIW, I'm using Apple's Mail.app, and it doesn't have a "reply-to- 
list".  In fact, I don't know of a mail client off the top of my head  
that does (certainly neither of the two that I use on a regular  
basis).  I just use 'reply-to-all' which is what many people on the  
haskell lists do (judging by the headers on email I receive).   
However, I don't recall problems with multiple copies of emails.  I  
think (pure speculation) the haskell.org mail server is set up to  
omit people from mail it sends if they appear in the To: or Cc: of  
the original mail.


Finally, I agree that reply-to munging is a bad idea, but I don't  
think appealing to a definition of 'reasonable mailer' that doesn't  
match a large portion of mail clients currently in the wild is a good  
way to argue the point.






* It removes important information, which can make it impossible to
get back to the message sender.


This is the most important bit, actually.  Anyone who wants to post a
single question to haskell or haskell-cafe has to be subscribed, or  
the

reply may go to the list, no matter what he put into the reply-to
header.  Is it a good thing to shut out casual users?



I view pine as something that should be classified as
reasonable


Pein (sic!) is not reasonable.  If you love it so much, please whip  
out

the source code, implement a "reply-to-list" function and get at least
one mailer removed from a silly debate.



I disagree.
I don't agree.
I don't agree.
I don't agree.
I don't agree.


Very convincing.  Keep up the good work.


Udo.
--
Hast du zum Leben kein Motiv --
steig mal vor, vielleicht geht's schief.
-- aus einem Gipfelbuch



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] beginner's problem about lists

2006-10-11 Thread Robert Dockins


On Oct 11, 2006, at 11:14 AM, Ross Paterson wrote:


On Wed, Oct 11, 2006 at 11:04:49AM -0400, Robert Dockins wrote:

let q = seq q (FinCons 3 q) in q(beta)

We have (from section 6.2):
   seq _|_ y = _|_
   seq x y = yiff x /= _|_

Now, here we have an interesting dilemma.


The meaning of a recursive definition is the least fixed point of
the equation, in this case _|_.  Same as let x = x in x.



Ah... of course!  A simple explanation; I hoped there was one.   
It's nice that it coincides with what I wanted the answer to be. :-)




Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] beginner's problem about lists

2006-10-11 Thread Robert Dockins


On Oct 11, 2006, at 10:14 AM, Malcolm Wallace wrote:


Matthias Fischmann <[EMAIL PROTECTED]> wrote:


No, your Fin type can also hold infinite values.


let q = FinCons 3 q in case q of FinCons i _ -> i  ==>  _|_

does that contradict, or did i just not understand what you are
saying?


That may be the result in ghc, but nhc98 gives the answer 3.

It is not entirely clear which implementation is correct.  The  
Language

Report has little enough to say about strict components of data
structures - a single paragraph in 4.2.1.  It defines them in terms of
the strict application operator ($!), thus ultimately in terms of seq,
and as far as I can see, nhc98 is perfectly compliant here.

The definition of seq is
seq _|_ b = _|_
seq  a  b = b, if a/= _|_

In the circular expression
let q = FinCons 3 q in q
it is clear that the second component of the FinCons constructor is  
not

_|_ (it has at least a FinCons constructor), and therefore it does not
matter what its full unfolding is.



Let's do some algebra.

data FinList a = FinCons a !(FinList a)


let q = FinCons 3 q in q
==>
let q = ((\x1 x2 -> (FinCons $ x1)) $! x2) 3 q in q   (translation  
from 4.2.1)

==>
let q = (FinCons $ 3) $! q in q (beta)
==>
let q = ($!) (($) FinCons 3) q in q (syntax)
==>
let q = ($!) ((\f x -> f x) FinCons 3) q in q   (unfold ($))
==>
let q = ($!) (FinCons 3) q in q (beta)
==>
let q = (\f x -> seq x (f x)) (FinCons 3) q in q(unfold ($!))
==>
let q = seq q (FinCons 3 q) in q(beta)


We have (from section 6.2):
   seq _|_ y = _|_
   seq x y = yiff x /= _|_


Now, here we have an interesting dilemma.  Suppose q is _|_, then:

let q = seq q (FinCons 3 q) in q
  ==>
let q = _|_ in q(specification of  
seq)

  ==>
_|_ (unfold let)


Instead suppose q /= _|_, then:

let q = seq q (FinCons 3 q) in q
  ==>
let q = FinCons 3 q in q(specification of  
seq)

  ==>
let q = FinCons 3 q in FinCons 3 q(unfold let)
  ==>
FinCons 3 (let q = FinCons 3 q in q)   (float let)



It seems that both answers are valid, in that they conform to the  
specification.  Is 'seq' under-specified?  Using a straightforward  
operational interpretation, you will probably get the first answer, _| 
_, and this is what I have always assumed.  The second requires a  
sort of strange "leap of faith" to arrive at that answer (ie, assume  
'q' is non-bottom), and is less satisfying to me.  What do others think?





Regards,
Malcolm



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] a monad for secret information

2006-10-10 Thread Robert Dockins


On Oct 10, 2006, at 12:04 PM, Seth Gordon wrote:


data Secret a = Secret {password :: String, value :: a}

classify :: String -> a -> Secret a
classify = Secret

declassify :: String -> Secret a -> Maybe a
declassify guess (Secret pw v) | guess == pw = Just v
| otherwise = Nothing

Put that in a module, do not export the Secret data type, and you're
good to go. I'm unsure what a Monad is giving you


I was just curious if I could do that within a monad.

If the answer to my question is "no, you can't", then I'll pick up the
shattered pieces of my life and move on.  :-)



I think you can.  Your original monad is just a little too  
simplistic.  Try something like this (untested):



import Control.Monad.State

type Password = String
type Secret s a = State (Password -> Maybe s) a

classify :: Password -> s -> Secret s ()
classify pw s = put (\x -> if x == pw then Just s else Nothing)

declassify :: Password -> Secret s (Maybe s)
declassify pw = get >>= \f -> return (f pw)

runSecret :: Secret s a -> a
runSecret m = runState m (const Nothing)


Note how this relies on "opaque" functions to hide the secret.  This  
wouldn't work if Haskell had intensional observation of functions,  
although you could still use a newtype in that case.



Slightly related: I've sometimes wondered about a monadic API for  
cryptographic primitives.  With compiler support you could do nifty  
things like make sure to use non-swappable memory for encryption keys  
and use fancy special purpose hardware for cryptographic primitives,  
if available.  The API would give a nice way to ensure proper  
information hiding policy.  Has anything like this been done or studied?




Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] Error building Edison 1.2.0.1

2006-10-05 Thread Robert Dockins
On Thursday 05 October 2006 16:51, Lyle Kopnicky wrote:
> Robert Dockins wrote:
> > On Wednesday 04 October 2006 16:16, Lyle Kopnicky wrote:
> >> Robert Dockins wrote:
> >>> Whats the output of
> >>>
> >>> ghc-pkg -l
> >>>
> >>> ?
> >>
> >> [EMAIL PROTECTED]:~$ ghc-pkg -l
> >> /usr/local/lib/ghc-6.5.20060924/package.conf:
> >> Cabal-1.1.4, base-2.0, (ghc-6.5.20060924), haskell98-1.0,
> >> parsec-2.0, readline-1.0, regex-base-0.71, regex-compat-0.71,
> >> regex-posix-0.71, rts-1.0, stm-2.0, template-haskell-2.0, unix-1.0
> >> l
> >
> > Hummm.  Well, I confess that I'm confused.  Cabal 1.1.4 should work,
> > because that's what I have on my machines; I've just tested it here.  The
> > only thing I can think of is that the 'runhaskell' command is still bound
> > to your old GHC, or to something else (Hugs maybe?).  If that's the case,
> > you can edit the makefile and set the 'RUNHS' variable in the first line
> > to the full path to your 6.5 runghc.  Or you can edit the .cabal files as
> > suggested above.
>
> I don't have hugs installed, and I've uninstalled ghc 6.4.1, so it can
> only be running 6.5.
>
> I've pasted the error in again here for reference:
> > [EMAIL PROTECTED]:~/devel/edison-1.2.0.1-source$ sudo make system
> > Password:
> > cd edison-api && \
> >   runhaskell Setup.hs configure && \
> >   runhaskell Setup.hs build && \
> >   runhaskell Setup.hs install
> > Configuring EdisonAPI-1.2...
> > configure: Dependency base>=1.0: using base-2.0
> > configure: Dependency haskell98>=1.0: using haskell98-1.0
> > Setup.hs: cannot satisfy dependency mtl>=1.0
> > make: *** [api-system] Error 1
> > [EMAIL PROTECTED]:~/devel/edison-1.2.0.1-source$
>
> Do you know what mtl is?

mtl is the Monad Transformer Library.  It's a part of the standard libraries 
in 6.4.x.  There's been a good deal of chatter recently about reducing the 
set of libraries the GHC ships with; it may be that mtl is on that list.  I 
haven't really been following, so I'm not sure.

> Maybe there's something broken in this GHC 
> snapshot. I've already noticed Template Haskell seems to be broken in it.

Possible.  I also notice that QuickCheck isn't in your list of installed 
packages.  You'll need that to compile edison-core.



> - Lyle

-- 
Rob Dockins

Talk softly and drive a Sherman tank.
Laugh hard, it's a long way to the bank.
   -- TMBG
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Error building Edison 1.2.0.1

2006-10-04 Thread Robert Dockins
On Wednesday 04 October 2006 16:16, Lyle Kopnicky wrote:
> Robert Dockins wrote:
> > On Tuesday 03 October 2006 22:58, Lyle Kopnicky wrote:
> >> Robert Dockins wrote:
> >>> On Tuesday 03 October 2006 22:00, Lyle Kopnicky wrote:
> >>>> Hi folks,
> >>>>
> >>>> I tried to build edison-1.2.0.1-sources with the command 'make system'
> >>>> but got:
> >>>>
> >>>> *** Exception: Line 10: Unknown field 'hs-source-dirs'
> >>>>
> >>>> I am using GHC 6.4.1. Any idea how to fix this?
> >>>
> >>> You are probably using an older version of Cabal.  You can either
> >>> upgrade Cabal or, from the Edison README*:
> >>>
> >>>
> >>> This version of edison builds correctly with Cabal version 1.1.4,
> >>> which is shipped with GHC 6.4.2.  To build on earlier versions,
> >>> it should suffice to:
> >>>
> >>> s/UndecidableInstances/AllowUndecidableInstances/
> >>> s/Hs-Source-Dirs:/Hs-Source-Dir:/
> >>>
> >>> in the .cabal files.
> >>>
> >>>
> >>>
> >>> The 'hs-source-dir' cabal directive was depreciated in 1.1.4, but
> >>> perhaps I should have waited a bit longer to change it.  OTOH, there
> >>> isn't any good way to deal with the change in the undecidable instances
> >>> flag, since it was outright changed.  G. *grumble* incompatible
> >>> changes in minor releases *grumble*.
> >>>
> >>>
> >>> (*) Further, g... in the above, I've fixed several embarrasing
> >>> typos in the text of the README.
> >>
> >> Oh, OK, thanks! Well, now I'm running GHC 6.5.20060924, and getting the
> >> error mentioned in my previous message.
> >
> > Whats the output of
> >
> > ghc-pkg -l
> >
> > ?
>
> [EMAIL PROTECTED]:~$ ghc-pkg -l
> /usr/local/lib/ghc-6.5.20060924/package.conf:
> Cabal-1.1.4, base-2.0, (ghc-6.5.20060924), haskell98-1.0,
> parsec-2.0, readline-1.0, regex-base-0.71, regex-compat-0.71,
> regex-posix-0.71, rts-1.0, stm-2.0, template-haskell-2.0, unix-1.0
> l

Hummm.  Well, I confess that I'm confused.  Cabal 1.1.4 should work, because 
that's what I have on my machines; I've just tested it here.  The only thing 
I can think of is that the 'runhaskell' command is still bound to your old 
GHC, or to something else (Hugs maybe?).  If that's the case, you can edit 
the makefile and set the 'RUNHS' variable in the first line to the full path 
to your 6.5 runghc.  Or you can edit the .cabal files as suggested above.


-- 
Rob Dockins

Talk softly and drive a Sherman tank.
Laugh hard, it's a long way to the bank.
   -- TMBG
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Error building Edison 1.2.0.1

2006-10-04 Thread Robert Dockins
On Tuesday 03 October 2006 22:58, Lyle Kopnicky wrote:
> Robert Dockins wrote:
> > On Tuesday 03 October 2006 22:00, Lyle Kopnicky wrote:
> >> Hi folks,
> >>
> >> I tried to build edison-1.2.0.1-sources with the command 'make system'
> >> but got:
> >>
> >> *** Exception: Line 10: Unknown field 'hs-source-dirs'
> >>
> >> I am using GHC 6.4.1. Any idea how to fix this?
> >
> > You are probably using an older version of Cabal.  You can either upgrade
> > Cabal or, from the Edison README*:
> >
> >
> > This version of edison builds correctly with Cabal version 1.1.4,
> > which is shipped with GHC 6.4.2.  To build on earlier versions,
> > it should suffice to:
> >
> > s/UndecidableInstances/AllowUndecidableInstances/
> > s/Hs-Source-Dirs:/Hs-Source-Dir:/
> >
> > in the .cabal files.
> >
> >
> >
> > The 'hs-source-dir' cabal directive was depreciated in 1.1.4, but perhaps
> > I should have waited a bit longer to change it.  OTOH, there isn't any
> > good way to deal with the change in the undecidable instances flag, since
> > it was outright changed.  G. *grumble* incompatible changes in
> > minor releases *grumble*.
> >
> >
> > (*) Further, g... in the above, I've fixed several embarrasing typos
> > in the text of the README.
>
> Oh, OK, thanks! Well, now I'm running GHC 6.5.20060924, and getting the
> error mentioned in my previous message.

Whats the output of

ghc-pkg -l

?


> - Lyle

-- 
Rob Dockins

Talk softly and drive a Sherman tank.
Laugh hard, it's a long way to the bank.
   -- TMBG
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Error building Edison 1.2.0.1

2006-10-03 Thread Robert Dockins
On Tuesday 03 October 2006 22:00, Lyle Kopnicky wrote:
> Hi folks,
>
> I tried to build edison-1.2.0.1-sources with the command 'make system'
> but got:
>
> *** Exception: Line 10: Unknown field 'hs-source-dirs'
>
> I am using GHC 6.4.1. Any idea how to fix this?

You are probably using an older version of Cabal.  You can either upgrade 
Cabal or, from the Edison README*:


This version of edison builds correctly with Cabal version 1.1.4,
which is shipped with GHC 6.4.2.  To build on earlier versions,
it should suffice to:

s/UndecidableInstances/AllowUndecidableInstances/
s/Hs-Source-Dirs:/Hs-Source-Dir:/

in the .cabal files.



The 'hs-source-dir' cabal directive was depreciated in 1.1.4, but perhaps I 
should have waited a bit longer to change it.  OTOH, there isn't any good way 
to deal with the change in the undecidable instances flag, since it was 
outright changed.  G. *grumble* incompatible changes in minor 
releases *grumble*.


(*) Further, g... in the above, I've fixed several embarrasing typos in 
the text of the README.

> Thanks,
> Lyle

-- 
Rob Dockins

Talk softly and drive a Sherman tank.
Laugh hard, it's a long way to the bank.
   -- TMBG
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Is Haskell a 5GL?

2006-09-29 Thread Robert Dockins

On Sep 28, 2006, at 8:47 PM, David Curran wrote:


Sorry if this comes across as the rant it is. If you are interested in
doing useful stuff rather then navel gazing please stop here.

Where are compute languages going?
I think multi core, distributed, fault tolerant.
So you would end up with a computer of the sort envisioned by Hillis
in the 80s with his data parallel programs. The only language that
seems even close to this model is Erlang. What am I missing about the
ability of Haskell to distribute across processors or a network?

Say instead of fault tolerant it is fault avoiding.
Can proving programs correct (with Haskell) really reduce our  
workload?

http://www.seas.upenn.edu/~sweirich/wmm/03-benton.pdf


I read that paper as saying formal methods have an extremely steep  
learning curve and large initial investment, but that the learning  
and initial investment pay off over time.  The author found that,  
even in the short time he worked with it, formal methods saved time  
when he needed to modify his definitions (third paragraph in the  
second column).  As with many automation tasks, the payoff comes with  
repeated identical or similar iterations.  Furthermore, his acquired  
knowledge transferred well to an unrelated project.  I can personally  
vouch for many of his experiences, having worked some with Coq myself.



Finally is Haskell a language for programming or a mental gymnasium
that might be the proving ground for concepts in the next popular
language? To quote from a post on the topic "Old functional
programming ideas " on programming.reddit.com


I don't know how much you agree with this quote, but for the purposes  
of discussion I'll assume that you have expressed these views  
personally.  You did, after all, preface your message by saying it  
was a rant so I'm going to assume you're prepared for the flames. ;-)



"Church-Turing equivalence tells us that all models of recursive
computing have the same formal power. But it tells us nothing about
which models are the most effective way for humans to understand and
express definitions of functions. For some reason I'd expect
researchers in programming languages to have a lot of opinions on this
subject. But they don't seem to talk about it much.


I think the Haskell community is doing better than many in this  
regard.  There is a concurrent thread on haskell-prime occurring  
_right now_ about whether pattern guards should be in Haskell'.  The  
primary point of disagreement is about whether pattern guards are a  
more effective way for humans to understand and express definitions  
of functions or not!  The ages-old disagreement about top-level state  
is similar, if more heated.  Similar for (n+k) patterns, and a host  
of other issues.  The endless discussions about monads often revolve  
around the goal of achieving new and better ways to express  
complicated function definitions.


I think this is because a fundamental value of the Haskell community  
is flexibility of the language.  Many languages are presented to the  
programmer as a complete package, which doesn't encourage them to  
consider the various possible design decisions that went into  
creating that language.  With Haskell, new users are often quickly  
confronted with various different ways of expressing their goals and  
with extensions they can enable (or not) and are forced to consider  
how best to express their program.  I think this is more good than it  
is bad.



Instead, a cynical and mean-spirited person might come to the
conclusion that PL researchers (such as Wadler) are actually just
mathematicians,


You seem to say this like its a bad thing; I completely disagree.  I  
don't think of myself as mean-spirited, and I have no problems  
calling, eg, Wadler a mathematician.  Just as I would call Church and  
Turing and Kleene and Goedel and Milner (etc, etc, etc)  
mathematicians.  If someone were ever to call _me_ a mathematician, I  
would consider it an honor.  Furthermore, if anyone attempted to  
belittle these distinguished persons or their accomplishments by  
calling them "just" mathematicians, I would begin to question his or  
her qualifications to have an opinion on the subject worthy of  
consideration.


The field mathematics has a long and glorious history of helping  
people to solve real problems.  I don't understand this undercurrent  
of antagonism that some people in our field have towards it.  Let's  
be honest: developing correct programs that perform non-trivial tasks  
and reasoning about them is HARD.  The techniques of mathematics and  
its sister discipline formal logic can help us with these tasks.  I  
find it a little strange that this position even requires a defense.   
All of the other scientific and engineering disciplines embrace the  
mathematics that help them do their work.  I don't believe there are  
very many physicists who would call Newton a mathematician and intend  
it to be a derogatory term.


I per

Re: [Haskell-cafe] Optimizing a title matcher

2006-09-26 Thread Robert Dockins
On Tuesday 26 September 2006 16:44, Lyle Kopnicky wrote:
> Hi folks,
>
> I'm competing in a contest at work, and we're allowed to use whatever
> language we want. I decided this was my chance to prove to people that
> Haskell was up to the challenge. Unfortunately, I ran into performance
> problems. Since the contest ends this Friday, I've decided to switch to
> C++ (gasp!). But if any of you have advice on how to speed up this code,
> it could help me advocate Haskell in the future.
>
> It's supposed to match movie titles from an imported database to a
> reference database. The version I've sent doesn't do anything very smart
> - it's just doing literal title matches. The first argument to the
> program is the filename of the table to be imported, and the second is
> the filename of the reference table. The first line of each table is a
> pipe-separated list of field names; the rest of the lines are records,
> each a pipe-separated list of values.
>
> The import files each have 3,000 records, and the reference table has
> 137,986 records.
>
> Building the hash tables out of the files is quick - it just takes a few
> seconds. But doing the matching of title_id in one table to title_id in
> the other, in a nested loop between both tables, takes way too long.
> It's matching two import titles (against each of the reference titles)
> per second. It needs to do at least 20 per second to qualify for the
> contest, and it's not doing anything fancy yet.

Humm... well, double nested loops seems like the wrong approach.  Also, if you 
are using GHC, it's hashtable implementation has farily well-known 
performance problems. If all you care about is exact matching, then the 
operation is essentially a finite map intersection (if I've understood what 
you are trying to do).

This is just a guess, but I suspect you will probably get much better 
performance (and better-looking code!) by just using Data.Map.intersection
 
http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data-Map.html#v%3Aintersection

Alternately, there is the ternary trie implementation from Edison 
(http://www.eecs.tufts.edu/~rdocki01) that may also work for you.

If you need to do prefix matching, then a trie is the way to go.  You can 
probably code up a nice prefix-intersection operation using tries that should 
go pretty fast.

If you have some other metric other than prefix in mind for partial matches, 
then things probably get a lot more complicated.  You're probably looking at 
calculating minimum distances in some feature-space, which calls for pretty 
sophisticated algorithms if you need good performance.

> I tried various "improvements" to speed it up. One was to specifically
> use ByteString, eliminating the AbsString class. Didn't make a
> difference. Another was to use arrays instead of lists to store each
> record, and precompute the indices of each of the fields within those
> records. I also iterated over a list of keys instead of the list of
> Maps, and only converted each record to a Map one at a time, hoping they
> would be disposed of sooner. Instead of speeding up the program, this
> slowed it down by a factor of 20!
>
> I've profiled it, and I can't make much out of that. It seemed to be
> spending 25% of its time doing scoring, and I though the problem must be
> due to laziness, but I'm not sure.
>
> So if anyone has any ideas how to speed this up by a factor of at least
> 10 times, it would be really appreciated! Even the Ruby solutions are
> doing that, which is embarrassing.
>
> Thanks,
> Lyle

-- 
Rob Dockins

Talk softly and drive a Sherman tank.
Laugh hard, it's a long way to the bank.
   -- TMBG
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Optimization problem

2006-09-19 Thread Robert Dockins


On Sep 19, 2006, at 8:52 AM, Conor McBride wrote:


Hi folks

[EMAIL PROTECTED] wrote:
Btw, why are there no irrefutable patterns for GADTs? I mean, such  
a sin

should be shame for a non-strict language...




Just imagine

> data Eq a b where Refl :: Eq a a

> coerce :: Eq a b -> a -> b
> coerce ~Refl a = b



I think you mean:

> coerce ~Refl x = x



coerce undefined True :: String

Bang you're dead. Or rather... Twiddle you're dead.

Moral: in a non-total language, if you're using indexing to act as  
evidence for something, you need to be strict about checking the  
evidence before you act on it, or you will be vulnerable to the  
blandishments of the most appalling liars.


As Randy Pollack used to say to us when we were children, the best  
thing about working in a strongly normalizing language is not  
having to normalize things.


All the best

Conor



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] Monad laws

2006-09-07 Thread Robert Dockins


On Sep 7, 2006, at 9:04 AM, Lennart Augustsson wrote:


Brian,

Are you really sure Haskell compilers do that optimization?
I would regard a compiler that does optimizations that are  
justified by laws that the compiler cannot check as broken.


What, like list fusion?

;-)

Although, more seriously, there are a number of "monads" in the  
standard libs that don't follow the monad laws (including IO http:// 
article.gmane.org/gmane.comp.lang.haskell.general/5273  !!).


I can't imagine that any haskell compilers rely on these laws to do  
program transformations.




-- Lennart

On Sep 7, 2006, at 08:50 , Brian Hulley wrote:


Deokhwan Kim wrote:

What is the practical meaning of monad laws?

(M, return, >>=) is not qualified as a category-theoretical  
monad, if

the following laws are not satisfied:

 1. (return x) >>= f == f x
 2. m >>= return == m
 3. (m >>= f) >>= g == m >> (\x -> f x >>= g)

But what practical problems can unsatisfying them cause? In other
words, I wonder if declaring a instance of the Monad class but not
checking it for monad laws may cause any problems, except for not
being qualified as a theoretical monad?


Afaiu the monad laws are needed so the compiler can do various  
optimizations, especially in regard to the "do" notation. Consider:


   g c = do
   if c
   then p
   else return ()
   q

Intuitively, the "else" branch of the "if" statement does nothing  
interesting, but we need to put something there because we can't  
just leave the branch empty, hence the use of (return ()), but  
thankfully, because of the monad laws, the compiler can apply  
transformations to get rid of it when it desugars the "do" notation.


The above is equivalent to:

   g c = (if c then p else return ()) >>= (\_ -> q)

which could be re-written as:

   g c = if c then (p >>= (\_ -> q)) else (return () >>= (\_ -> q))

which can be optimized using monad law 1) to:

   g c = if c then (p >>= (\_ -> q)) else (\_ -> q) ()

which can further be optimized to:

   g c = if c then (p >>= (\_ -> q)) else q

so when the condition (c) is False we don't waste time doing the  
(return ()) action, but go straight to (q).


However if your monad didn't satisfy the laws, the compiler would  
still assume that it did thus leading to a flawed "optimization"  
ie the compiler would throw your program away and substitute it  
for a different, unrelated, program...


Regards, Brian.
--
Logic empowers us and Love gives us purpose.
Yet still phantoms restless for eras long past,
congealed in the present in unthought forms,
strive mightily unseen to destroy us.

http://www.metamilk.com




Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] getContents and lazy evaluation

2006-09-01 Thread Robert Dockins
On Friday 01 September 2006 18:01, Donn Cave wrote:
> On Fri, 1 Sep 2006, Robert Dockins wrote:
> > On Friday 01 September 2006 16:46, Duncan Coutts wrote:
>
> ...
>
> >> Note also, that with lazy IO we can write really short programs that are
> >> blindingly quick. Lazy IO allows us to save a copy through the Handle
> >> buffer.
>
> (Never understood why some people think it would be such a good thing
> to be blinded, but as long as it's you and not me ... )
>
> >> BTW in the above case the "bad thing that will happen" is that contents
> >> will be truncated. As I said, I think it's better to throw an exception,
> >> which is what Data.ByteString.Lazy.hGetContents does.
> >
> > Well, AFAIK, the behavior is officially undefined, which is my real beef.
> >  I agree that it _should_ throw an exception.
>
> Is this about Microsoft Windows?  On UNIX, I would expect deletion of
> a file to have no effect on I/O of any kind on that file.  I thought
> the problems with hGetContents more commonly involve operations on
> the file handle, e.g., hClose.

Ahh... I think you're right.

However, this just illustrates the problem.  The point is that the answer the 
question "what happens when I do " is "it 
depends".  And to the obvious followup question "what does it depend on?" the 
answer is "well it's complicated".

>   Donn Cave, [EMAIL PROTECTED]

-- 
Rob Dockins

Talk softly and drive a Sherman tank.
Laugh hard, it's a long way to the bank.
   -- TMBG
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] getContents and lazy evaluation

2006-09-01 Thread Robert Dockins
On Friday 01 September 2006 16:46, Duncan Coutts wrote:
> On Fri, 2006-09-01 at 16:28 -0400, Robert Dockins wrote:
> > On Friday 01 September 2006 15:19, Tamas K Papp wrote:
> > > Hi,
> > >
> > > I am newbie, reading the Gentle Introduction.  Chapter 7
> > > (Input/Output) says
> > >
> > >   Pragmatically, it may seem that getContents must immediately read an
> > >   entire file or channel, resulting in poor space and time performance
> > >   under certain conditions. However, this is not the case. The key
> > >   point is that getContents returns a "lazy" (i.e. non-strict) list of
> > >   characters (recall that strings are just lists of characters in
> > >   Haskell), whose elements are read "by demand" just like any other
> > >   list. An implementation can be expected to implement this
> > >   demand-driven behavior by reading one character at a time from the
> > >   file as they are required by the computation.
> > >
> > > So what happens if I do
> > >
> > > contents <- getContents handle
> > > putStr (take 5 contents) -- assume that the implementation
> > >-- only reads a few chars
> > > -- delete the file in some way
> > > putStr (take 500 contents) -- but the file is not there now
> > >
> > > If an IO function is lazy, doesn't that break sequentiality?  Sorry if
> > > the question is stupid.
> >
> > This is not a stupid question at all, and it highlights the main problem
> > with lazy IO.  The solution is, in essence "don't do that, because Bad
> > Things will happen".  It's pretty unsatisfactory, but there it is.  For
> > this reason, lazy IO is widely regarded as somewhat dangerous (or even as
> > an outright misfeature, by a few).
> >
> > If you are going to be doing simple pipe-style IO (ie, read some data
> > sequentially, manipulate it, spit out the output),  lazy IO is very
> > convenient, and it makes putting together quick scripts very easy. 
> > However, if you're doing something more advanced, you'd probably do best
> > to stay away from lazy IO.
>
> Since working on Data.ByteString.Lazy I'm now even more of a pro-lazy-IO
> zealot than I was before ;-)
>
> In practise I expect that most programs that deal with file IO strictly
> do not handle the file disappearing under them very well either.

That's probably true, except for especially robust applications where such a 
thing is a regular (or at least expected) event.

> At best 
> the probably throw an exception and let something else clean up. The
> same can be done with lazy I, though it requires using imprecise
> exceptions which some people grumble about. So I would contend that lazy
> IO is actually applicable in rather a wider range of circumstances than
> you might. :-)

Perhaps I should be more clear.  When I said "advanced" above I meant "any use 
whereby you treat a file as random access, read/write storage, or do any kind 
of directory manipulation (including deleting and or renaming files)".  Lazy 
I/O (as it currently stands) doesn't play very nice with those use cases.

I agree generally with the idea that lazy I/O is good.  The problem is that it 
is a "leaky abstraction"; details are exposed to the user that should ideally 
be completely hidden.  Unfortunately, the leaks aren't likely to get plugged 
without pretty tight operating system support, which I suspect won't be 
happening anytime soon.

> Note also, that with lazy IO we can write really short programs that are
> blindingly quick. Lazy IO allows us to save a copy through the Handle
> buffer.

> BTW in the above case the "bad thing that will happen" is that contents
> will be truncated. As I said, I think it's better to throw an exception,
> which is what Data.ByteString.Lazy.hGetContents does.

Well, AFAIK, the behavior is officially undefined, which is my real beef.  I 
agree that it _should_ throw an exception.

> Duncan

-- 
Rob Dockins

Talk softly and drive a Sherman tank.
Laugh hard, it's a long way to the bank.
   -- TMBG
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] getContents and lazy evaluation

2006-09-01 Thread Robert Dockins
On Friday 01 September 2006 15:19, Tamas K Papp wrote:
> Hi,
>
> I am newbie, reading the Gentle Introduction.  Chapter 7
> (Input/Output) says
>
>   Pragmatically, it may seem that getContents must immediately read an
>   entire file or channel, resulting in poor space and time performance
>   under certain conditions. However, this is not the case. The key
>   point is that getContents returns a "lazy" (i.e. non-strict) list of
>   characters (recall that strings are just lists of characters in
>   Haskell), whose elements are read "by demand" just like any other
>   list. An implementation can be expected to implement this
>   demand-driven behavior by reading one character at a time from the
>   file as they are required by the computation.
>
> So what happens if I do
>
> contents <- getContents handle
> putStr (take 5 contents) -- assume that the implementation
>-- only reads a few chars
> -- delete the file in some way
> putStr (take 500 contents) -- but the file is not there now
>
> If an IO function is lazy, doesn't that break sequentiality?  Sorry if
> the question is stupid.

This is not a stupid question at all, and it highlights the main problem with 
lazy IO.  The solution is, in essence "don't do that, because Bad Things will 
happen".  It's pretty unsatisfactory, but there it is.  For this reason, lazy 
IO is widely regarded as somewhat dangerous (or even as an outright 
misfeature, by a few).

If you are going to be doing simple pipe-style IO (ie, read some data 
sequentially, manipulate it, spit out the output),  lazy IO is very 
convenient, and it makes putting together quick scripts very easy.  However, 
if you're doing something more advanced, you'd probably do best to stay away 
from lazy IO.

Welcome to Haskell, BTW  :-)

> Thanks,
>
> Tamas

-- 
Rob Dockins

Talk softly and drive a Sherman tank.
Laugh hard, it's a long way to the bank.
   -- TMBG
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Exercise in point free-style

2006-09-01 Thread Robert Dockins
On Friday 01 September 2006 11:44, Neil Mitchell wrote:
> Hi
>
> > func2 f g l = filter f (map g l)
> > is
> > func2p f g = (filter f) . (map g)
>
> func2 = (. map) . (.) . filter
>
> Again, how anyone can come up with a solution like this, is entirely
> beyond me...

To answer part of the OP's question, it's always possible to rewrite a lambda 
term using point-free style (using a surprisingly small set of basic 
combinators).  The price you pay is that the new term is often quite a bit 
larger than the old term.  Rewriting complicated lambda terms as point-free 
terms is often of, em, dubious value.  OTOH, it can be interesting for 
understanding arrows, which are a lot like monads in points-free style (from 
what little experience I have with them).

BTW, the process of rewriting can be entirely automated.  I assume the 
lambdabot is using one of the well-known algorithms, probably tweaked a bit.

Goolge "combinatory logic" or "Turner's combinators" if you're curious.


> Thanks
>
> Neil


-- 
Rob Dockins

Talk softly and drive a Sherman tank.
Laugh hard, it's a long way to the bank.
   -- TMBG
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: A free monad theorem?

2006-08-31 Thread Robert Dockins
> So getting the value out of the monad is not a pure function (extract ::
> Monad m => m a -> a). I think I stated that, already, in my previous post.
> I'd even say that the monadic values alone can be completely meaningless.
> They often have a meaning only relative to some environment, thus are
> (usually) _effectful_ computations. But we already knew that, didn't we?

It may help to remember that, in the mathematical context where monads where 
born (AKA category theory), a monad is generally defined as a functor with a 
join and a unit (satisfying some laws that I would have to look up).  The 
unit should be familiar (it's spelled 'return' in haskell), but join may not 
be.  Its type is

join :: Monad m => m (m a) -> m a

which is a lot like extract, except with one more "monad layer" wrapped around 
it.  IIRC the relevant identity here is:

x >>= f === join (fmap f x)

and with f specialzed to id:

join (fmap id x) === x >>= id
join x   === x >>= id

I'm not sure why (>>=) is taken as basic in Haskell.  At any rate, my point is 
that I think your questions might be better framed in terms of the behavior 
of 'fmap'.

> The real question (the one that bugs me, anyway) is if one can give a
> precise meaning to the informal argument that if the definition of bind is
> to be non-trivial then its second argument must be applied to some
> non-trivial value at one point (but not, of course, in all cases, nor
> necessarily only once), and that this implies that the computation
> represented by the first argument must somehow be 'run' (in some
> environment) in order to produce such a value. -- And, of course, whether
> this is actually true in the first place. Would you say that your examples
> above are counter-examples to this statement (imprecise as it is,
> unfortunately)?

> Ben




-- 
Rob Dockins

Talk softly and drive a Sherman tank.
Laugh hard, it's a long way to the bank.
   -- TMBG
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [Parsec] A combinator to match between M and N times?

2006-08-29 Thread Robert Dockins


On Aug 29, 2006, at 9:11 AM, Tomasz Zielonka wrote:


On Tue, Aug 29, 2006 at 03:05:39PM +0200, Stephane Bortzmeyer wrote:

Parsec provides "count n p" to run the parser p exactly n times. I'm
looking for a combinator "countBetween m n p" which will run the
parser between m and n times. It does not exist in Parsec.



Much to my surprise, it seems quite difficult to write it myself and,
until now, I failed (the best result I had was with the "option"
combinator, which unfortunately requires a dummy value, returned when
the parser fails).


How about this?

countBetween m n p = do
xs <- count m p
ys <- count (n - m) $ option Nothing $ do
y <- p
return (Just y)
return (xs ++ catMaybes ys)

Assuming n >= m.


Does anyone has a solution? Preferrably one I can understand, which
means not yet with liftM :-)


No liftM, as requested :-)


Here's an interesting puzzle.  For a moment, consider parsec only wrt  
its language-recognition capabilities.


Then, we expect the count combinator to factor,

count x p >> count y p === count (x+y) p

where === mean "accepts the same set of strings".


I somehow intuitively expect the countBetween combinator to factor in  
a similar way also, but it doesn't (at least, none of the posted  
versions do)!  Note the output of:


parser1 = countBetween 3 7 (char 'a') >> eof
parser2 = countBetween 2 3 (char 'a') >> countBetween 1 4 (char 'a')  
>> eof


main = do
  print $ parse parser1 "" "aaa"
  print $ parse parser2 "" "aaa"


OK.  What's happening is that the greedy nature of the combinator  
breaks things because parsec doesn't do backtracking by default.  I'd  
expect to be able to insert 'try' in the right places to make it  
work.  However, after playing around for a few minutes, I can't  
figure out any combination that does it.  Is it possible to write  
this combinator so that it factors in this way?




Best regards
Tomasz




Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] Derived Read instance for types with infix constructors (ghc 6.4.1)

2006-08-25 Thread Robert Dockins


On Aug 25, 2006, at 6:50 PM, Misha Aizatulin wrote:


hi,

  the Haskell Report 10.4 says that

"The result of show is readable by read if all component types are  
readable"


  however if I define a type like

data T = A | T `And` T deriving (Read, Show)

  then

*Main> show $ A `And` A
"A And A"
*Main> (read "A And A") :: T
*** Exception: Prelude.read: no parse
*Main>

  In fact, I wasn't able to guess, what I should type so that the  
value

(A `And` A) gets parsed.

  I have ghc 6.4.1. Looking into the code of the derived instance I  
see

that it expects Text.Read.Lex.lex to return (Symbol "And") for the
constructor. If I understand the code for lex correctly, then it  
parses

things as Symbol if they consist only of
"[EMAIL PROTECTED]&*+./<=>?\\^|:-~"

  How then do I read values of type T defined above? Thanks in advance
for any directions.



In general, derived Read instances are designed to be inverses for  
Show.  The easy thing to do is to print values of type T and see what  
you get.  I expect that it will be in prefix form, eg:


And A A

or

And (And A A) A

etc.

That is, I think the Show and Read instances are going to ignore the  
backticks in the definition.




Cheers,
  Misha



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG

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


Re: [Haskell-cafe] a novice Alex question

2006-08-25 Thread Robert Dockins


On Aug 25, 2006, at 6:27 AM, Xiong Yingfei wrote:


Hi,

I am trying out Alex. I copied the calculator specification file  
from Alex's official document and changed the wrapper type from  
"basic" to "monad". However, after I generated the ".hs" file from  
the lexical specification and compiled the ".hs" file, I got the  
message "Variable not in scope: `alexEOF'". I cannot find  
explanation about this 'alexEOF' function in the document. Can any  
body be kindly enough to tell me what this function is? Should I  
write it myself or not? My lexical code is listed as the below.  
Thanks a lot.


You should provide alexEOF.  The idea is that it is a special token  
representing the end of input.  This is necessary because the monad  
wrapper doesn't deliver a list of tokens like the basic wrapper, so  
it needs some way to signal the end of input.  The easiest thing to  
do is add a constructor to your token datatype, and then just set  
alexEOF to that constructor:


data Token =
   
   | EOFToken


alexEOF = EOFToken





{
module Lex where

}

%wrapper "monad"

$digit = 0-9   -- digits
$alpha = [a-zA-Z]  -- alphabetic characters

tokens :-

  $white+;
  "--".*;
  let { \s -> Let }
  in { \s -> In }
  $digit+{ \s -> Int (read s) }
  [\=\+\-\*\/\(\)]   { \s -> Sym (head s) }
  $alpha [$alpha $digit \_ \']*  { \s -> Var s }

{
-- Each action has type :: String -> Token

-- The token type:
data Token =
 Let   |
 In|
 Sym Char |
 Var String |
 Int Int
 deriving (Eq,Show)
}

--
Xiong, Yingfei (熊英飞)
Ph.D. Student
Institute of Software
School of Electronics Engineering and Computer Science
Peking University
Beijing, 100871, PRC.
Web: http:// 
xiong.yingfei.googlepages.com_ 
__



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] implementing a csv reader

2006-08-23 Thread Robert Dockins


On Aug 23, 2006, at 3:37 PM, Henk-Jan van Tuyl wrote:



L.S.,

Reading and writing a comma seperated datafile doesn't have to be  
that complicated; the following is an easy way to read a CSV file  
into a list of tuples and display the list on screen:


"For every complex problem, there is a solution which is simple,  
neat, and wrong."  -- HL Mencken



Although it seems straightforward at first, CSV suffers from text  
escaping complexities, just as does every other general purpose plain- 
text encoding.  Most notably, a newline embedded inside double quotes  
does not end a record.  These issues cause ugly corner cases if you  
aren't expecting them.  And that's just the issues with moving tables  
of strings around; if those fields have non-string interpretations  
(dates or numbers or what have you), things get really hairy.  To do  
the "right thing" probably requires perl-ish duck typing  :-p


See http://www.creativyst.com/Doc/Articles/CSV/CSV01.htm for a semi- 
authoritative reference on CSV.  A related RFC is here: http:// 
tools.ietf.org/html/rfc4180




Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] extreme newbie: hugs prompt vs load module

2006-08-23 Thread Robert Dockins


On Aug 23, 2006, at 10:16 AM, George Young wrote:


[linux, ghci 6.4.3.20060820, hugs May 2006]

I have just started learning Haskell.  I have hugs and ghci under
linux, and I'm going through the Gentle Introduction to
Haskell, so far through section 4,
"case expressions and pattern matching".  I'm a python programmer,  
with

background in maclisp, scheme, T, C, C++, and a little J.

I'm confused about what sort of things I can type at the interpreter
prompt, and what things have to be loaded as a module.  I keep trying
to treat the prompt like a lisp or python REPL, which is obviously
wrong.  Can someone set me straight?


For the most part, the things you can enter at the GHCi or Hugs  
prompt are _expressions_.  This mostly* excludes _declarations_,  
which are things like function definitions, datatype declarations,  
class and instance declarations, etc.  Those things need to go into a  
source file.


(*) 'let' expressions will allow you to define local functions as  
part of an expression, however.  GHCi also has a slight variation of  
'let' that allows you to define functions for the session.




Is there another tutorial that might be more appropriate for me?


The following tutorial is generally recognized as one of the better  
ones:


http://www.cs.utah.edu/~hal/htut/


I am finding haskell quite appealing.  I hope to start writing real  
(if
small) applications to do some data analysis from our Postgres DB.   
Any

hints?


There are several haskell database layers.  I've had some luck with  
HDBC, which has a PostgreSQL driver.


http://quux.org:70/devel/hdbc



--George Young
--
"Are the gods not just?"  "Oh no, child.
What would become of us if they were?" (C.S. Lewis)




Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] Haskell wiki: most popular pages

2006-08-18 Thread Robert Dockins


On Aug 18, 2006, at 12:23 PM, Tim Walkenhorst wrote:


Bulat Ziganshin wrote:

i think that definitions with omitted arguments can be more hrd to
understand to newbie haskellers, especiallyones who not yet know the
language. as Tamas suggests, this page can be used to present to such
newbies taste of Haskell so listing all the parameters may allow to
omit unnecessary complications in this "first look into language"

I agree with that. The and = ... wasn't really an improvement over  
and xs = ... xs, and if the later is easier to read that's good.


Btw.:

What happened to isSpace, toLower and toUpper (, from the  
tutorial)? (I)sSpace must be there for words anyway, so I can't see  
why it's missing. (T)oLower and toUpper might have some subleties  
with internationalization and stuff, but they would be useful for  
me even as a poor man's version which can just convert "A-Z", "a-z"  
and no umlauts.



http://www.haskell.org/ghc/docs/latest/html/libraries/base/Data- 
Char.html



I feel that Haskell is missing some basic string manipuation  
functions, like
- replacing all occurances of one substring (or sublist) with  
another string (or list).

- tokenize a string by an arbitrary delimeter

I know many of these functions can be written in Haskell without  
much effort. But I don't really want to "invent" isSpace for any  
program.


Tim



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] More threading confusion

2006-08-17 Thread Robert Dockins


On Aug 17, 2006, at 3:48 PM, Creighton Hogg wrote:


Good afternoon Haskellers,

So I'm trying to understand how STM works, and wrote a quick  
'eating philosophers' example to see if I understood how it's  
supposed to work.
The problem is that while it executes, it doesn't appear to *do*  
anything.


Did I completely write things wrongheadedly or am I being bitten by  
something more subtle?


From a quick read, it looks like your program doesn't produce any  
output until a philosopher finishes 1 think/eat iterations.   
Something tells me that could take awhile




Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] The Q Programming Language can do symbolic manipulation -- Haskell?

2006-08-16 Thread Robert Dockins


On Aug 15, 2006, at 11:43 PM, Casey Hawthorne wrote:


The Q Programming Language can do symbolic manipulation -- Haskell?

The Q Programming Language can do the following:

sqr X = X*X

==>sqr 5
25

==>sqr (X+1)
(X+1)*(X+1)



Can Haskell do symbolic manipulation?



Well, there's always the sledgehammer (http://www.haskell.org/ghc/ 
docs/latest/html/users_guide/template-haskell.html)




Or are term-rewriting and the lambda calculus sufficiently far enough
apart concepts?
--
Regards,
Casey
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] Abstract Data Types

2006-08-09 Thread Robert Dockins


On Aug 9, 2006, at 5:27 AM, Johan Grönqvist wrote:


Hi,

I have a question:

Short version: If I want to hide the implementation of a data-type  
"Stack a" from the rest of the program,  do I need to put its  
definition in a separate file?




This is the usual way, as you've probably gathered.



Long version:

I want to use a stack, and I might implement it as a list, but I  
want to hide the implementation from the rest of the program. This  
is how I understand abstract data type.


In "The Craft of Functional Programming", this seems to be  
implemented by putting each data type into a separate module and  
only exporting parts of the definitions.


In "The Haskell School of Expression", this seems not to be used at  
all.


In the lecture notes at (http://www.dcs.shef.ac.uk/~mps/courses/ 
com2020/adts.pdf), type classes are used for abstract data types.  
It seems to me that this approach does not hide any parts of any  
definition, but only requires that all instances of class stack  
have functions pop and push of the correct types. I am interested  
in hiding parts of definitions.


In the report, I did not find any mention of a requirement to have  
different modules in separate files, but I have not managed to put  
several modules in the same file using ghci.



I think all current implementations require separate files for  
separate modules, although I believe you are correct that is is not  
required by the report.



I would like to keep my small program in one literate-haskell tex- 
file and still be able to hide some definitions from others.


Is this possible?

One option would of course be to write a script that separates the  
code into different and then compiles the entire program.




There are two other basic ways that I know of to achieve data type  
abstraction.



1) Parametric polymorphism

Create a typeclass with the appropriate operations.  Then, in  
functions which use stack operations, always write, eg:



doSomething :: Stack s => s a -> Bool

rather than

doSomething :: ConcreteStackType a -> Bool



This is abstraction "at the point of use" if you will.  You'll see  
this technique pretty often used to abstract over different Monads,  
for example.




2) Exestential datatypes.  You can create a sort of poor-man's  
substitute for ML style module systems by using existential data  
types.  Its a little fiddly, but it mostly works:



{-# OPTIONS -fglasgow-exts #-}

import Data.Maybe (isJust)


data StackRec a = forall s. Show (s a) => StackRec (s a) (a -> s a ->  
s a) (s a -> s a) (s a -> Maybe a)

listStackRec =
   StackRec
  []
  (:)
  (\xs -> case xs of (_:ys) -> ys; [] -> [])
  (\xs -> case xs of (y:_) -> Just y; [] -> Nothing)


fauxModule :: IO ()
fauxModule =
  case listStackRec of { StackRec empty push pop peek -> do

print (isJust (peek (pop (pop (push 'a' empty)
print (push 'b' empty)

-- doesn't typecheck
--print (push 'c' [])

  }

main = fauxModule




Unfortunately, the case statement gives you monomorphic bindings for  
the stack methods, and let bindings don't play nice with  
existentials.  I'm not sure if there's a way around this or not.




Thanks in advance!

/ johan grönqvist



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] Why Not Haskell?

2006-08-09 Thread Robert Dockins

On Aug 8, 2006, at 5:36 PM, Albert Lai wrote:


"Brian Hulley" <[EMAIL PROTECTED]> writes:


Also, the bottom line imho is that Haskell is a difficult language to
understand, and this is compounded by the apparent cleverness of
unreadable code like:

 c = (.) . (.)

when a normal person would just write:

 c f g a b = f (g a b)


All mainstream languages are also difficult to understand, with
similarly clever, unreadable code.  Let's have a fun quiz!  Guess the
mainstream languages in question:


[snip]


2. What language allows you to test primality in constant runtime?
   That is, move all the work to compile time, using its polymorphism.


GHC-Haskell (with enough extensions enabled)?  We're most of the way  
there already with type arithmetic.  I bet putting together a nieve  
primality test would be pretty doable.  In fact, I suspect that GHC's  
type-checker is turing-complete with MPTCs, fundeps, and undecidable  
instances.  I've been contemplating the possibility of embedding the  
lambda calculus for some time (anybody done this already?)


Oops.  I see now the qualifier "mainstream".  The point still stands,  
however.



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] Why shouldn't variable names be capitalized?

2006-08-04 Thread Robert Dockins


On Aug 4, 2006, at 1:12 PM, Martin Percossi wrote:

Hi, I'm wondering what the rationale was for not allowing  
capitalized variable names (and uncapitalized type names and  
constructors). I can only think of two arguments, and IMHO both of  
them are bad:


1. Enforces a naming convention. Fine - but my view is that this  
doesn't belong in the language definition (it belongs in the user's  
coding standards). I get annoyed, for example, that when I write  
code that manipulates matrices and vectors, I can't refer to the  
matrices with capital letters as is common in the literature.


This is occasionally irritating.

And to anyone who says that it's good to enforce naming  
consistency, I have this to say: Any language that requires me to  
learn about category theory in order to write imperative code  
should treat me like an adult when it comes to the naming of  
variables as well. ;-)


2. It makes it easier to write the compiler. I don't think I need  
to explain why this is bad...


Eh?  I'm not convinced this is a bad reason.  It obviously needs to  
be balanced against other competing factors, but ease of  
implementation should always a consideration when designing a language.



3. It removes a whole class of possible ambiguities from the  
language.  You the programmer (and the compiler, as an added bonus)  
can always identify the syntactic class of an identifier from _purely  
local_ context.


Suppose I remove the case restriction.  Is the following a pattern  
match or a function definition?  Is M a variable or a data constructor?


   let f x M = z M in 

You can't tell!  Worse, it could change depending on what identifiers  
are in scope.  It could happen that you import a module and it  
silently causes your function definition to change to a pattern  
match.  The situation is similar with type classes and type  
variables.  You could magically end up with an instance declaration  
that is less polymorphic than you expect (if you have extensions  
turned on).


I imagine that someone is just itching to "sort me out". Do your  
worst! ;-)


Thx
Martin



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] Edison StandardSet has inefficient function implementation

2006-08-03 Thread Robert Dockins

On Aug 3, 2006, at 7:14 AM, Ahn, Ki Yung wrote:

Edision does not yet have all the asymtotic description of its  
functions.


Indeed.  This is a big job which requires a lot of time, attention to  
detail, and a pretty good working understanding of lazy amortized  
analysis.  Unfortunately I'm currently lacking in categories 1 and 3...


Many of the bounds can be obtained from the referenced papers.  I'll  
work on adding those as I am able.



I got the Edision 1.2 source and looked into the code whether the
container implementations meet the expected asymtotic bounds.



In the module Data.Coll.StandardSet which packages Data.Set,
some functions which can be O(log n) is implemented as O(n).

Data.Set has a split and splitMember running in O(log n).
With those functions we can implement OrdCollX operations like
filterLT, filterLE, filterGT, filterGE,
partitionLT_GE, partitionLE_GT, partitionLT_GT all in O(log n).
However, only partitionLT_GT was O(log n) implemended using split.
All other function implmentation just used its axiomaic description
using CollX operations like filter and partition, which is O(n).


Thanks for pointing this out.  filterLT and filterGT can indeed be  
written in terms of "split"; I just missed that somehow.


For the others, however, splitMember won't suffice.  The problem here  
is that splitMember doesn't return the "equal" member from the  
original set, it just returns a Bool indicating whether the set  
contained and "equal" element.  As of now, Edison is supposed to  
guarantee that, for observable collections, you will always get back  
the identical object(s) that you put in.  This accounts for the fact  
that you may supply an Eq instance which is only a weak equivalance,  
that is, even if x == y returns true, x and y may be distinguishable  
in some way.


I am considering dropping this guarantee in a future version of  
Edison, because I think its value is highly dubious.  (Using a set or  
bag with a weak element equivalence is really just creating a finite  
map/relation.  If you need a finite map/relation you should just  
_use_ a finite map/relation!)  If I dropped the guarantee, I could  
indeed implement the other operations as you suggest.





It needs to be fixed.

P.S. I haven't checked the darcs version yet.

--
Ahn, Ki Yung



Thanks for your comments!



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


[Haskell-cafe] Future Edison directions

2006-08-01 Thread Robert Dockins

Hello all,

There has been very recently a thread discussing the design decisions  
involved in creating a sequence abstraction.  This was naturally of  
interest to me as the current Edison maintainer, and generated a fair  
bit of interesting discussion.  I'd like to kick off a new thread  
here to talk about future directions for the Edison API in particular.


1) Regarding Sequence, I have become convinced by the discussion that  
the Edison Sequence class should be broken down into smaller  
classes.  Furthermore, it would be very nice to make these smaller  
classes shared across the various families of data structure  
abstractions in Edison (Sequences, Collections and Associative  
Collections).  The formulation of Sequence of kind * -> * may need to  
be sacrificed to this end.  I am not convinced that losing the maps  
and zips would be a major blow; however there are a couple of  
strategies for retaining them in some form.


2) The associated collection API is in a similar situation, except  
there are no zips.


3) I am reluctant to undertake a major overhaul of the Edison API  
while the future of type classes in Haskell' is so hazy.  I haven't  
heard any news from the Haskell' type classes focus group in quite  
some time, and last I was aware, discussion was somewhat stalled.  I  
there any hope for a coherent story here in the nearish future?


4) I am on the verge of deciding that nobody wants non-observable  
collections (ie, collections in which the element values are not  
available for inspection).  Currently Edison has no implementations  
which are non-observable, and I am not aware of anyone else creating  
a datastructure implementation in Haskell which is non-observable.   
Therefore, I am considering removing this feature of the Edison  
typeclass hierarchy to reduce complexity.  Shout if you think this  
would be a terrible mistake.


5) OTOH, something people DO seem to want is collection "views", or  
the ability to treat a datastructure as though it were something  
else.  For example, it would be nice to transparently treat the keys  
of a finite map as a set, or to treat a nested sequence as a single  
flattened sequence.  Such uses require the separation of operations  
which can create datastructures from those which merely inspect them  
(or some fancy bidirectional stuff I don't think I want to get into).


6) Edison 1.2 has now been out for a couple of months.  If you've  
used or looked at the new Edison, I'd love to hear what you think.  I  
think the next development cycle will involve pretty substantial  
changes, and if you want to get your gripes addressed, now is a good  
time to voice them.  Alternately, if you think there are some aspects  
that are very important to keep, that's also good information.


7) Finally, I somehow feel like there should be a nice categorical  
formulation of these datastructure abstractions which would help to  
drive a refactoring of the API typeclasses in a principled way,  
rather than on an ad-hoc I-sort-of-think-these-go-together sort of  
way.  Unfortunately, my category-fu is quite weak, so all I have is  
this vague intuition that I can't substantiate.  I'm sort of familiar  
with initial algebras, but I think they may be too concrete.  I'm  
looking for some way to classify algebras that have, eg, the property  
of having folds, or of being set-like, etc.  If anybody can point me  
in the right direction wrt this, that would be great.




Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-08-01 Thread Robert Dockins


On Jul 31, 2006, at 10:27 PM, John Meacham wrote:

[snip]



It is best to think of haskell primitives as something completely new,
they reuse some naming conventions from OO programming, but that  
doesn't

mean they suffer from the same limitations. It took me a few trys to
wrap my brain around it. I liken learning haskell to tipping over a
vending machine. you can't just push it, you gotta rock it back and
forth a few times building up momentum until bam! suddenly the  
flash of

insight hits and it all makes sense.



Do you have a lot of personal experience attaining zen-like insight  
by tipping over vending machines? I'll have to try that some time ;-)


*chucke*

Thanks for making me laugh this morning.




John



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-31 Thread Robert Dockins

On Jul 30, 2006, at 5:28 PM, Brian Hulley wrote:

Robert Dockins wrote:

On Sunday 30 July 2006 07:47, Brian Hulley wrote:

Another option, is the Edison library which uses:

 class (Functor s, MonadPlus s) => Sequence s where

so here MonadPlus is used instead of Monoid to provide empty and
append. So I've got three main questions:



1) Did Edison choose MonadPlus just because this fitted in with the
lack of multi-parameter typeclasses in H98?

Edison's design hails from a time when MPTCs were not only
non-standard (as they still are), but also not widely used, and
before fundeps were avaliable (I think).  So the answer to this one
is pretty much "yes".

[snip]

Hi - Thanks for the answers to this and my other questions. One  
thing I just realised is that there doesn't seem to be any instance  
declarations anywhere in the standard libs relating Monoid to  
MonadPlus so it's a bit unsettling to have to make a "random"  
choice on the question of what kind of object a Sequence is...


I tried:

   class (forall a. Monoid s a) => Sequence s where ...

but of course that doesn't work, so I suppose MonadPlus is the only  
option when 'a' doesn't appear as a type variable arg of the class  
being defined.



BTW, for what purpose are you desiging a new sequence class?  You are
clearly aware of other efforts in this area; in what ways to they not
meet your needs?


The existing sequence and collection classes I've looked at don't  
do enough.


For example, when I tried to represent the text in an edit widget,  
I realised I needed a sequence of characters that could also be  
considered to be a sequence of lines, and it is necessary to be  
able to index the sequence by character position as well as by line  
position, as well as keeping track of the total number of  
characters, the total number of lines, and the maximum number of  
characters on any one line (so as to be able to calculate the x,y  
extents when laying out the widget, assuming a fixed width font  
(tabs ignored!)), with very efficient split and append operations.


So, what you want is a sequence of sequences that can be  
transparently converted to a "flattened" sequence and vice versa? And  
you also want to keep track of the total number of lines and  
characters within each line.  Additionally, you want to keep track of  
the maximum number of characters in any one line.


I managed to get a good representation by using a FingerTree of  
lines where each line uses a ByteString.
I made my own FingerTree class based on the one referenced in the  
paper at http://www.soi.city.ac.uk/~ross/papers/FingerTree.html but  
without the symbolic names which I find totally unreadable and  
confusing, and also so I could get full control of the strictness  
of the implementation, and also as a way of understanding them  
since I'd never come across such a complicated data structure  
before. (I highly recommend this paper to anyone who wants to learn  
about FingerTrees, Monoids and other very useful concepts.)


So one thing existing sequence classes don't have (apart from  
FingerTree) is the concept of measurement which is essential when  
you want efficient updates. Eg in my text buffer, the measurement  
maintained for a sequence is the number of chars and number of  
lines and maximum line length.


Edison has support for transparently keeping track of the size of a  
sequence.


http://www.eecs.tufts.edu/~rdocki01/docs/edison/Data-Edison-Seq- 
SizedSeq.html


It may well be possible to create a slightly generalized wrapper that  
keeps track of arbitrary "measures".  (If they can be computed by a  
function which is associative, commutative and has a unit).

Humm, sort of an incremental fold I like it.

Then I needed a structure for a Trie widget a bit like (details  
omitted):


 data Node = Expanded Value T | Collapsed Value T | Leaf Value
 newtype T = T (FingerTree (Key, Node))

where objects of type T could be regarded as a finite map (eg from  
hierarchical module names to modules) as well as a flattened linear  
sequence indexed by line number (for display on the screen in a  
widget given the current scroll bar position), and which also  
needed to keep track of the total horizontal and vertical extent of  
the Trie as it would appear in the widget's font.


There are several different kinds of measurement going on in this  
data structure, as well as the complexity of the extra recursion  
through the leaf to a new level. Existing sequence abstractions  
don't seem to provide the operations needed to treat a nested data  
structure as a single sequence.


In summary:

1) Often a complex data structure must be able to be simultaneously  
regarded as a single flattened sequence
2) Measurements are needed for efficient updates (may need to keep  
track of several at once)
3) Indexing and size are someti

Re: [Haskell-cafe] The difficulty of designing a sequence class

2006-07-30 Thread Robert Dockins
On Sunday 30 July 2006 07:47, Brian Hulley wrote:
> Hi -
>
> Part 1 of 2 - Monoid versus MonadPlus
> ===
>
> I've just run into a troublesome question when trying to design a sequence
> class:
>
> class ISeq c a | c -> a where
>  empty :: c
>  single :: a -> c
>  append :: c -> c -> c
>
> However I've noticed that people sometimes separate the empty and append
> operations out as sequences with these ops form a Monoid therefore:
>
>  class Monoid c => ISeq c a | c -> a where
>  single :: a -> c
>
>  -- now outside the class
>  append :: ISeq c a => c -> c -> c
>  append = mappend
>
>  empty :: ISeq c a => c
>  empty = mempty
>
> Another option, is the Edison library which uses:
>
>  class (Functor s, MonadPlus s) => Sequence s where
>
> so here MonadPlus is used instead of Monoid to provide empty and append.
> So I've got three main questions:

> 1) Did Edison choose MonadPlus just because this fitted in with the lack of
> multi-parameter typeclasses in H98?

Edison's design hails from a time when MPTCs were not only non-standard (as  
they still are), but also not widely used, and before fundeps were avaliable 
(I think).  So the answer to this one is pretty much "yes".  I've considered 
reformulating the Sequence class to be more similar to the Collection classes 
(which use MPTCs, fundeps and mention the element type), but for the 1.2 
version I wanted to make as few changes as I thought I could to the overall 
design decisions.

In fact, I will likely make this change at some point.  It would allow, eg, 
making Don's ByteString (or whatever it's called now, I forget) an instance 
of Sequence, which is currently impossible.  OTOH, it would require 
sacrificing the Functor, Monad and MonadPlus instances...

> 2) Are there any reasons to prefer the Edison design over the MPTC design
> (apart from H98 compatibility) or vice versa?

H98 is probably the big one.  I'm currently in wait-and-see mode concerning 
MPTCs and especially fundeps.  As Edison maintainer, I've tried to use them 
sparingly in the hope that Edison can be made Haskell' compliant (crosses 
fingers).  Aside: I hope the Haskell' committee makes some sort of decision 
here soonish.

> 3) Is it worth bothering to derive ISeq from Monoid (with the possible
> extra inefficiency of the indirection through the definitions for append =
> mappend etc or does the compiler completely optimize this out)?

Not sure about this one.  I suspect, however, that the appropriate SPECIALIZE 
pragmas could cover any cases that you really care about.

> and a fourth more long term question:
>
> 4) Would it be worth reconsidering the rules for top level names so that
> class methods could always be local to their class (ditto for value
> constructors and field names being local to their type constructor).

[snip more question]

No comment.

> Part 2 of 2 - Monad versus Ancillary result type
> 
>
> Another issue relates to left and right views of a sequence. If a sequence
> is non-empty, the left view is just the leftmost element and the rest of
> the sequence. The problem arises when the sequence is empty. In the Edison
> library, this is solved by returning a monadic value ie:
>
>  lview :: Monad m => s a -> m (a, s a)
>
> whereas from the paper "Finger trees: a simple general purpose data
> structure" by Ralf Hinze and Ross Paterson they use an ancillary data type
> to store the result of a view:
>
> data ViewL s a = NilL | ConsL a (s a)
>
> viewL :: FingerTree a -> ViewL FingerTree a
>
> So my question here is: what's the best choice? I can see that the monadic
> version has the advantage that it could be used in do notation in cases
> where you expect the sequence to be non-empty, but has the disadvantage
> that it treats the empty sequence as something special (resulting in
> Monad/fail) and an extra indirection to find the components when the
> sequence is non-empty.

Well, the empty sequence IS special, when it comes to looking the leftmost 
(resp. righmost) element.  You have to deal somehow with the fact that the 
operation is a partial function.

I think the arbitrary monad option is better.  It gives the user more 
flexibility about how to use the operation.  Really the only way to use ViewL 
is to put it inside a "case of".  With a monad you can use any of the 
plethora of monadic operations and, as you mentioned, the do notation.  In 
addition, if you want the use case of ViewL, you can always use the Maybe 
monad.

I'm not inclined to worry too much about the extra indirection, which seems 
like a viable target for being erased by the compiler (I've not tested if 
this happens, however).


> Anyway these are my main questions for now - any feedback appreciated ;-)


BTW, for what purpose are you desiging a new sequence class?  You are clearly 
aware of other efforts in this area; in what ways to they not meet your 
needs

Re: [Haskell-cafe] Re: ANN: System.FilePath 0.9

2006-07-26 Thread Robert Dockins


On Jul 26, 2006, at 1:47 PM, Neil Mitchell wrote:


Hi,


Perhaps instead:

   directoryOf :: FilePath -> String
   filenameOf  :: FilePath -> String
   extensionOf :: FilePath -> String
   basenaneOf  :: FilePath -> String

   replaceFilename  = joinFilePath . directoryOf
   replaceDirectory = flip joinFilePath . filenameOf


Trying to design a consistent naming system, it helps if we all agree
on what the various parts of a filepath are called, this is my draft
of that:

http://www-users.cs.york.ac.uk/~ndm/temp/filepath.png

With a better name for basename, if anyone can think of one.


"stem", perhaps?  You could also, maybe, distinguish the "short  
stem" (everything before the "extensions") from the "long stem"  
everything before the "extension".




Once we have that, how about

takeElement :: FilePath -> String
dropElement :: FilePath -> String
replaceElement :: FilePath -> String -> FilePath
addElement :: FilePath -> String -> FilePath
splitElement :: FilePath -> (String, String)
joinElement :: String -> String -> FilePath

With the restriction that not all of these are provided. Some don't
make sense (splitBaseName, dropBaseName), some are implemented via
combine (addFileName, joinFileName), some are redundant (addExtensions
== addExtension)

I'm also debating whether split/join should be exported, since they
are less likely to be used and can easily be written as a take/drop
pair. And of course, a bigger interface is harder to understand.

Opinions on this? It's easier to tweak a specification than the  
actual code :)


Thanks

Neil



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


[Haskell-cafe] Re: [Haskell] rigid variables

2006-07-20 Thread Robert Dockins

[moved to cafe]

On Jul 20, 2006, at 12:48 PM, Rodney D Price wrote:

I've gotten this sort of error several times, which mysteriously  
disappears

when I add more functions to the code:

storeError.hs:13:38:
Couldn't match expected type `a' (a rigid variable)
   against inferred type `String'
  `a' is bound by the type signature for `throwError'
at 
  Expected type: a
  Inferred type: String
In the first argument of `return', namely `msg'
In the call (return msg)

(This is GHCi.)  The code is below.  The type variable a can't be  
bound to
String, obviously, but a relative novice like myself has no idea  
why.  Can

someone tell me?

Thanks,

-Rod

--
module Store where

import Control.Monad.Error
import Control.Concurrent.STM

data StoreError = Default String

instance Error StoreError where
noMsg  = Default "Store error"
strMsg = Default

instance MonadError StoreError STM where
throwError (Default msg) = return msg



Lets take a look here at the definition of MonadError from  
Control.Monad.Error:


class Monad m => MonadError e m | m -> e where
throwError :: e -> m a
catchError :: m a -> (e -> m a) -> m a


In the signature for 'throwError' there are three type variables: e,  
m and a.  e and m are bound by the instance declaration, but a is  
free.  In Haskell the rule is that free variables are implicitly  
bound with a universal quantifier.  So, the type for throwError can  
be regarded as,


throwError :: forall a. e -> m a,  for some concrete choices of  
e and m which are determined by the instance.


The forall means that a user of this function can put any type there  
that he likes.  In other words, the monadic action created by  
'throwError', when executed, evaluates to _a value of any type at  
all_ (yes, I know the terminology is a little loose here).  That  
means you can't just 'return msg', which has type 'm String' because  
a user might have used throwError to create an action of type 'm  
Int', for example.  In fact, you won't really be able to return  
anything at all, because there isn't any way to write a program that  
can generate a value of any unknown type.  This should hopefully  
correspond to your intuition about what throwing an exception does.


The error generated by the typechecker basically tells you that the  
function you have written is not polymorphic enough.  It has type  
'StoreError -> STM String' rather than 'forall a. StoreError -> STM  
a' as it ought.


I think perhaps you have misunderstood how MonadError is used.  The  
idea is to expose to users a particular non-local control flow  
construct (throw/catch style exceptions) by hiding all the stuff  
necessary for that inside the monad plumbing.  Usually, whoever  
writes the monad itself will provide the necessary instances.  It's  
often not possible to write instances like this by using the external  
API of the monad.  This is particularly the case for the abstract  
monads available in GHC (IO, ST, and STM).


In short, I don't think you'll be successful in writing a  
'MonadError' instance for STM that has the customary semantics.  What  
you may be looking for is the ErrorT monad transformer, which will  
let you layer error handling over STM.  It's hard to know with what  
info you've provided here.  If you give a few more details on what  
you're trying to accomplish, someone may be able to give you a push  
in the correct direction.




Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] Comma in the front

2006-07-13 Thread Robert Dockins


On Jul 12, 2006, at 9:18 PM, Joel Reymont wrote:


Are cool kids supposed to put the comma in front like this?

, foo
, bar
, baz

Is this for historical or other reasons because Emacs formats  
Haskell code well enough regardless.


Thanks, Joel



I personally like this style.  It's a little hard to say why, but let  
me attempt.  I think it's related to layout.  Layout trained me to  
regard the end of lines as uninteresting, and the beginning as  
interesting.  Thus, I forget to put separators at the ends of lines  
(freedom from the tyranny of the semicolon!), but I always notice if  
a comma or semicolon is missing at the beginning of a line.  Its very  
obvious because they're all aligned vertically and, as I said,  
Haskell trains you to notice the leading edges of lines if you use  
layout.  It also makes it very visually obvious where the list/tuple/ 
do block ends when you line up the brackets with the separators.


IMO the patch/diff/darcs issue is a red herring.  It sounds like an  
after the fact justification to me.



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] help with creating a DAG?

2006-07-08 Thread Robert Dockins
On Saturday 08 July 2006 12:25 pm, David Roundy wrote:
> Hi all,
>
> I'm wanting to create a data structure to hold a directed acyclic
> graph (which will have patches represented by edges), and haven't yet
> been able to figure out a nice representation.  I'd like one that can
> be reasoned with recursively, or as closely to recursively as
> possible.  The problem is one of dependency relations between darcs
> patches, and "normally" reduces to a simple tree, with conflict
> resolution patches bringing branches of the tree back together.  Trees
> I know how to handle intuitively and elegantly, but DAGs are a whole
> different question.
>
> I looked for papers, and there was one on "an initial-algebra approach
> to DAGs" that looked promising, but I'm afraid I wasn't able to fully
> understand it, and it is able to describe more complicated DAGs than
> I'd like to support.
>
> Anyhow, any suggestions from persons with experience with this sort of
> thing would be great.  These are getting to be data structures that
> are more complicated than anything I'm comfortable with.  :(


Is there some reason you don't want to use FGL?

http://web.engr.oregonstate.edu/~erwig/fgl/haskell/
http://haskell.org/ghc/docs/latest/html/libraries/fgl/Data-Graph-Inductive.html



-- 
Rob Dockins

Talk softly and drive a Sherman tank.
Laugh hard, it's a long way to the bank.
   -- TMBG
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Prefix/Infix operators

2006-07-07 Thread Robert Dockins


On Jul 7, 2006, at 8:57 AM, Sara Kenedy wrote:


Hello everybody,

I checked the topics in Haskell-Cafe about prefix/infix operators but
I did not find them. Now I bring my questions to here to ask you.

1) I have a Common-Lisp code representing an expression result as  
follows

((MPLUS SIMP)
  ((MTIMES SIMP) ((RAT SIMP) 1 2) ((MEXPT SIMP) $X 2))
  ((MTIMES SIMP) ((RAT SIMP) 1 3) ((MEXPT SIMP) $X 3)))

2) I attempted to change it to mathematics operators, replacing

MPLUS SIMP -> +
MEQUAL SIMP -> =
RAT SIMP   -> /
MEXPT SIMP -> ^


[snip some code]


3) And NOW I want to transfer from prefix operator into infix
operator, for example: From
((+)
  ((*) ((/) 1 2) ((^) x 2))
  ((*) ((/) 1 3) ((^) x 3)))

in to the expression: 1/2*x^2+1/3*x^3

I try to figure out it, but this time it is not successfully. If you
are familiar with that, please share with me. Many thanks to all.


If I were approaching this problem, I'd probably think of it like a  
very small compiler.  That is, I would 1) define the abstract syntax  
as a algebraic data type 2) parse the S-expression into the abstract  
syntax and 3) pretty-print the new concrete syntax with infix operators.


Even for a language as small as this one, I think the benefits of  
approaching the problem in a modular way outweigh the overhead.  I  
think it would be very difficult to get, eg, operator precedence  
correct by just doing text manipulations on the string.


Of course, since the source is s-expressions anyway, there's always  
the option of writing a lisp macro to do the whole thing and thereby  
get parsing for free.



As a mostly related aside, here's a cool looking tutorial google  
turned up about writing a scheme interpreter in Haskell:


http://halogen.note.amherst.edu/~jdtang/scheme_in_48/tutorial/ 
overview.html




Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG


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


[Haskell-cafe] Re: [Haskell] Re: ANNOUNCE: HNOP 0.1

2006-06-30 Thread Robert Dockins

[moved to cafe]

On Jun 30, 2006, at 4:01 AM, Ashley Yakeley wrote:


In article
<[EMAIL PROTECTED] 
>,

 "Bayley, Alistair" <[EMAIL PROTECTED]> wrote:


Cool, that's awesome. But I don't see any Haddock docs? Or a Cabal
Setup.hs? Would it be much trouble to add them?


Bear in mind HNOP compiles just to an executable file, so it doesn't
really have a Haskell API.

One interesting line of development would be to spin off the core
functionality into a separate library, to provide no-op services to
other Haskell applications.



I'm sorry; I know this is a serious discussion (either that or  
everyone involved in this discussion has a more subtle sense of humor  
than I), but this sentence made me laugh out loud...  :-)


"no-op services"?  That's just great!



I'm thinking something like this:

  noop :: IO ()  -- generalise to other Monads?

This would actually not be too hard to write, given my existing work,
and then of course the executable would simply be a thin wrapper.

--
Ashley Yakeley
Seattle WA




Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG

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


Re: [Haskell-cafe] Packages and modules

2006-06-25 Thread Robert Dockins
On Sunday 25 June 2006 05:16 am, Brian Hulley wrote:
> Hi -
> At the moment there is a problem in that two packages P and Q could contain
> the same hierarchical module eg Data.Foo, and the only way for user code to
> ensure the "right" Data.Foo is used is to ensure that packages P and Q are
> searched in the right order.
> However suppose P and Q also contain another module with the same name, eg
> Data.Bar.
> And suppose a user module wants to use Data.Foo from P but Data.Bar from
> Q!!!
>
> I'm wondering: would it not be easier to just make it that the package name
> is prepended to the hierarchical module name, so the modules would instead
> be called by the names P.Data.Foo and Q.Data.Bar?

[snip discussion of this idea]

The idea of improving the module system has been discussed a number of times 
before.  Here is a thread started by a suggestion from the simons which 
generated a fair bit of discussion:

http://www.haskell.org/pipermail/libraries/2003-August/001310.html

I'm not sure whatever became of this idea; discussion seemed to sort of reach 
a consensus, and then nothing happened.

The module "grafting" mechanism always seemed kind of nice to me.  I think 
some of the problems discussed in this thread could be by using cabal, 
especially to specify the graftings expected for compilation.  It seems like 
grafting can give a plausible story for dealing with dynamicly loaded code, 
which is a nice bonus.


-- 
Rob Dockins

Talk softly and drive a Sherman tank.
Laugh hard, it's a long way to the bank.
   -- TMBG
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Functional progr., images, laziness and all therest

2006-06-22 Thread Robert Dockins


On Jun 22, 2006, at 10:16 AM, Brian Hulley wrote:


minh thu wrote:

2006/6/22, Brian Hulley <[EMAIL PROTECTED]>:

Jerzy Karczmarczuk wrote:

Brian Hulley wrote:

[snip]
y IS NOT a longer list than yq, since co-recursive equations  
without

limiting cases, apply only to *infinite* streams. Obviously, the
consumer of such a stream will generate a finite segment only, but
it is his/her/its problem, not that of the producer.

I still don't understand this point, since y = (a*x0 : yq) so surely
by induction on the length of yq, y has 1 more element?

y and yq are infinite...


But how does this change the fact that y still has 1 more element  
than yq?

yq is after all, not a circular list.
I don't see why induction can't just be applied infinitely to prove  
this.


Induction doesn't apply to co-inductive objects, such as infinite  
lists AKA streams.


I particular, the "length" of an infinite list is undefined, much as  
the "size" of an infinite set is undefined.  The only think you can  
discuss, a la Cantor, is cardinality.  In both cases, as mentioned by  
another poster, it is aleph-null.



Every few months a discussion arises about induction and Haskell  
datatypes, and I feel compelled to trot out this oft-misunderstood  
fact about Haskell: 'data' declarations in Haskell introduce co- 
inductive definitions, NOT inductive ones.  Induction, in general,  
does not apply to ADTs defined in Haskell; this is in contrast to  
similar-looking definitions in, eg, ML.  This is a common source of  
confusion, especially for mathematically-inclined persons new to  
Haskell.  Does anyone know of a good reference which clearly explains  
the difference and its ramifications?  I've never been able to find a  
paper on the topic that doesn't dive head-first into complicated  
category theory (which I usually can't follow) ...




Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG

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


Re: [Haskell-cafe] Re: Functional programming for processing of largeraster images

2006-06-21 Thread Robert Dockins


On Jun 21, 2006, at 3:30 PM, Brian Hulley wrote:


Joel Reymont wrote:

I think the issue wasn't using functional programming for large image
processing, it was using Haskell. OCaml is notoriously fast and
strict. Haskell/GHC is... lazy.

Everyone knows that laziness is supposed to be a virtue. In practice,
though, I'm one of the people who either can't wrap their heads
around it or just find themselves having to fight it from the start.


Perhaps laziness is more "foundational", in that you can write

 if2 c x y = if c then x else y


[snip some conversation...]


For those who haven't seen this already, here is a presentation by  
Simon PJ in which he discusses his views on laziness (among other  
things).


http://research.microsoft.com/~simonpj/papers/haskell-retrospective/ 
HaskellRetrospective.pdf



Takeaway point about laziness: "Laziness keeps you honest" by not  
allowing you to slip in side effects.


Bonus takeaway: read Wadler's papers :-)



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG

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


Re: [Haskell-cafe] Computing lazy and strict list operations at the same time

2006-06-19 Thread Robert Dockins


On Jun 19, 2006, at 12:50 PM, Duncan Coutts wrote:


On Mon, 2006-06-19 at 17:03 +0100, Jon Fairbairn wrote:

On 2006-06-19 at 15:24- "C Rodrigues" wrote:
Here's a puzzle I haven't been able to solve.  Is it possible to  
write the

initlast function?

There are functions "init" and "last" that take constant stack  
space and
traverse the list at most once.  You can think of traversing the  
list as

deconstructing all the (:) [] constructors in list.

init (x:xs) = init' x xs
  where init' x (y:ys) = x:init' y ys
init' _ [] = []

last (x:xs) = last' x xs
  where last' _ (y:ys) = last' y ys
last' x [] = x

Now, is there a way to write initlast :: [a] -> ([a], a) that  
returns the
result of init and the result of last, takes constant stack  
space, and
traverses the list only once?  Calling reverse traverses the list  
again.  I
couldn't think of a way to do it, but I couldn't figure out why  
it would be

impossible.



il [] = error "foo"
il [x] = ([], x)
il (x:xs) = cof x (il xs)
where cof x ~(a,b) = (x:a, b)
--  !



From a quick test, it looks like none of our suggested solutions

actually work in constant space.



main = interact $ \s ->
  case il s of
(xs, x) -> let l = length xs
   in l `seq` show (l,x)

using ghc:
ghc -O foo.hs -o foo
./foo +RTS -M10m -RTS < 50mb.data

using runhugs:
runhugs foo.hs < 50mb.data

in both cases and for each of the three solutions we've suggested the
prog runs out of heap space where the spec asked for constant heap  
use.



Actually, the OP asked for constant stack space, which is quite  
different and much easier to achieve.




So what's wrong? In my test I was trying to follow my advice that we
should consume the init before consuming the last element. Was that
wrong? Is there another way of consuming the result of initlast that
will work in constant space?



That is, nonetheless, an interesting question.



Note that by changing discarding the x we do get constant space use:
main = interact $ \s ->
  case il s of
(xs, x) -> let l = length xs
   in l `seq` show l  -- rather than 'show (l,x)'

Why does holding onto 'x' retain 'xs' (or the initial input or some
other structure with linear space use)?

Duncan



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG

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


Re: [Haskell-cafe] Computing lazy and strict list operations at the same time

2006-06-19 Thread Robert Dockins


On Jun 19, 2006, at 11:24 AM, C Rodrigues wrote:

Here's a puzzle I haven't been able to solve.  Is it possible to  
write the initlast function?


There are functions "init" and "last" that take constant stack  
space and traverse the list at most once.  You can think of  
traversing the list as deconstructing all the (:) [] constructors  
in list.


init (x:xs) = init' x xs
 where init' x (y:ys) = x:init' y ys
   init' _ [] = []

last (x:xs) = last' x xs
 where last' _ (y:ys) = last' y ys
   last' x [] = x

Now, is there a way to write initlast :: [a] -> ([a], a) that  
returns the result of init and the result of last, takes constant  
stack space, and traverses the list only once?  Calling reverse  
traverses the list again.  I couldn't think of a way to do it, but  
I couldn't figure out why it would be impossible.



initlast :: [a] -> ([a],a)
initlast (x:xs) = f x xs id
where
  f x (y:ys) g = f y ys (g . (x:))
  f x [] g = (g [],x)



Its within the letter, if maybe not the spirit of the rules.  The  
accumulated function could arguably be considered to be traversing  
the list again.  FYI, the technique is a fairly well known one for  
overcoming the quadratic behavior of repeated (++).



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG

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


Re: [Haskell-cafe] Lambda abstraction analogous to imperative pseudo-code?

2006-06-10 Thread Robert Dockins
On Saturday 10 June 2006 04:35 pm, Clifford Beshers wrote:
> The Wikipedia article on lambda abstractions
> (http://en.wikipedia.org/wiki/Lambda_abstraction) has a statement that
> does not resonate with me:
>
> A lambda abstraction is to a functional programming
>  language such
> as Scheme 
> what pseudo-code  is to an
> imperative programming
>  language.
>
> Does anyone else find this to be a peculiar statement?  If you think it
> is accurate, could you provide an alternate explanation and/or example
> to the one in the article?

I agree; The article is questionable at best.  I've never seen the term 
"lambda abstraction" used in the way it is in the article.  I'd go so far as 
to say it's downright wrong.

This one is much better:

http://foldoc.org/foldoc.cgi?lambda+abstraction

-- 
Rob Dockins

Talk softly and drive a Sherman tank.
Laugh hard, it's a long way to the bank.
   -- TMBG
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Tips for converting Prolog to typeclasses?

2006-05-31 Thread Robert Dockins
On Wednesday 31 May 2006 08:22 pm, Greg Buchholz wrote:
> Lately, in my quest to get a better understanding of the typeclass
> system, I've been writing my typeclass instance declarations in Prolog
> first, then when I've debugged them, I port them over back over to
> Haskell.  The porting process involves a lot trial and error on my part
> trying to decide when to use functional dependencies and which compiler
> extension to enable ( -fallow-undecidable-instances,
> -fallow-overlapping-instances, etc.).  Which might be okay, but I still
> can produce things that won't compile, and I don't necessarily know if
> I'm making a fundamental mistake in a program, or if there's something
> trivial that I'm not doing quite right.
>
> For example, there was a question on haskell-cafe last week about
> creating an "apply" function.  My first solution (
> http://www.haskell.org//pipermail/haskell-cafe/2006-May/015905.html )
> was to use type classes and nested tuples for the collection of
> arguments.  This works fine.  But then I wanted to try to get closer to
> what the original poster wanted, namely to use regular homogenous lists
> to store the arguments.  So I thought I could reuse the class definition
> and just provide new instances for a list type, instead of the nested
> tuple type.  Here's the class definition...
>
> > class Apply a b c | a b -> c where
> > apply :: a -> b -> c
>
> ...So I wrote the following Prolog snippets which seemed like they might
> properly describe the situation I was looking for...
>
> :- op(1000,xfy,=>).  % use => instead of -> for arrow type
>
> app(A=>B,[A],C) :- app(B,[A],C).
> app(C,[A],C).
>
> ...which I translated into the following Haskell instances...
>
> > instance Apply b [a] c => Apply (a->b) [a] c where
> > apply f [] = error "Not enough arguments"
> > apply f (x:xs) = apply (f x) xs
> > instance Apply c [a] c where
> > apply f _ = f


To make this work, you're going to have to convince the compiler to accept 
"overlapping instances" and then make sure they don't overlap :) In the 
second instance, what you really want to say is "instance c [a] c, only where 
c is not an application of (->)".  As I recall, there is a way to express 
such type equality/unequality using typeclasses, but I don't remember how to 
do it offhand.


A quick google turns up this page, which appears to address most of the 
questions at hand:

http://okmij.org/ftp/Haskell/types.html


> ...and here's a test program...
>
> > g :: Int -> Int -> Int -> Int -> Int
> > g w x y z = w*x + y*z
> >
> > main = do print $ apply g [1..]
>
> ...but I haven't been able to get GHC to accept this yet.  So I'm
> wondering if there's an easy route to learning this stuff.  Some sort of
> comprehensive tutorial out there which I should be reading that
> describes what should be possible with Haskell's typeclasses plus GHC
> extenstions, and when and where to enable these extentions.  (Bonus
> points awarded if it explains things in terms of Prolog).  Or is this
> just one of those things that requires reading lots of papers on each
> extentsion and possibly the source code of the implementation?
>
> Thanks,
>
> Greg Buchholz
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe

-- 
Rob Dockins

Talk softly and drive a Sherman tank.
Laugh hard, it's a long way to the bank.
   -- TMBG
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] (.) . (.)

2006-05-28 Thread Robert Dockins
On Sunday 28 May 2006 05:50 pm, you wrote:
> [moved to cafe]
>
> Robert Dockins wrote:
> > On Sunday 28 May 2006 05:02 pm, Brian Hulley wrote:
> >> I see my error was that I was reversing the args in eta expansion,
> >> so the correct derivation is:
> >
> > FYI, eta-expansions isn't valid in Haskell.  Its safe in this
> > derivation, but it isn't always.
>
> Am I right in thinking that this is because of _|_ ?

Yup.  Well, _|_ and seq, really. IIUC, the removal of seq restores the 
validity of eta-conversion.

seq _|_ x = _|_

but,
 
seq (\z -> _|_ z) x = x


> In any case I suppose I should have instead just replaced the function with
> it's definition like you (view Lambda Shell) and Christophe did.
>
> Also, is your Lambda Shell publicly available? (I had a quick look on the
> wiki in the Theorem provers section but couldn't find a link.)

http://www.eecs.tufts.edu/~rdocki01/lambda.html

I've never thought of it as a theorem prover before ;-)

You can also play with it on #haskell via the lambdabot '@lam' command.
I think it binds to a slightly older version, but there aren't many 
user-visible changes.

> Thanks, Brian.

-- 
Rob Dockins

Talk softly and drive a Sherman tank.
Laugh hard, it's a long way to the bank.
   -- TMBG
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell RPC

2006-05-25 Thread Robert Dockins

On May 25, 2006, at 2:25 PM, Jason Dagit wrote:

On 5/25/06, Joel Reymont <[EMAIL PROTECTED]> wrote:


This is an example from my test harness:

(define-test remote-basic
   (def-remote-class remote (server) ())
   (def-remote-method sum :sync ((self remote) (a fixnum) (b  
integer))

  (declare (ignorable ip port))
  (+ a b seqnum))
   (let* ((port (+ 1000 (random 5)))
  (server (make-instance 'remote
 :port port))
  (client (make-instance 'remote-proxy
 :host (host-address)
 :port port)))
 (assert-equal '(6) (sum client 1 2 :seqnum 3))
 (stop server)
 (stop client)
 ))



I won't comment on the difference between haskell and lisp (both
languages I respect), but I will say that you should add a macro or
high order function (depneding on lisp vs. haskell) that is something
like "(with-client (c args-list)  body)", that way you can simplify
the creation/cleanup of clients. Same idea as with-open-file.  You can
do the same with server.

As for your actual question, there is a deriving(Read), but I don't
remember what extensions are needed.


None.  'deriving' for Read and Show are both Haskell 98.  It won't  
work for functions though.  Haskell functions, unlike in lisp/scheme,  
are "opaque".  If all you want to do is send data around, then you  
can surely use Read/Show, or some of the more efficient workalikes  
from DrIFT (http://repetae.net/~john/computer/haskell/DrIFT/).



Joel Raymont:
I think I can send Haskell code over the wire to be read on the  
other side just like I do with Lisp. The part that baffles me is  
being able to provide an interface that lets one easily define  
remote classes and methods.


I totally hate Template Haskell because I find it incomprehensible  
and I'm not going to compare it to Lisp macros. Is there a way to  
do it without TH?


If you want to deliver source code to be executed elsewhere, you can  
use hs-plugins or the GHC API (in GHC HEAD branch).  Check out the  
lambdabot for inspiration (http://haskell.org/haskellwiki/ 
Lambdabot).  Or you could maybe do something interesting here with  
YHC bytecode.  If you instead want to go the XML-RPC route there's  
HaXR (http://www.haskell.org/haxr/).


I can understand the sentiment about TH, but it's probably the only  
way to get a similar interface to the lisp one, short of  
preprocessing/code generation.


Beyond that, I'd say there are a few too many free variables in the  
problem description.  What would be the design goals and non-goals  
for such an RPC mechanism? What problems prompted the original lisp  
implementation? What about fault tolerance, reliability, security? etc.



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG

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


[Haskell-cafe] Re: [Haskell] TypeCasting in Haskell

2006-05-24 Thread Robert Dockins


On May 24, 2006, at 7:30 AM, Christophe Poucet wrote:

Dear all,

I typically use indirect composite for making AST's. It allows me  
to easily make new types with other annotations without having to  
duplicate all elements but only those that actually change. It also  
allows a whole amalgam of other possibilities. Recently I have  
observed a type error which seems to be fixable only by doing a  
"typecast". What do I call a typecast, you may ask? Basically a  
noop that changes the type. Here attached you will find the code  
that demonstrates this.


Is there a specific question in here?


module TypeCast where

data FooBar foo bar = --- Indirect composite
Foo { unFoo :: foo}
| Bar { unBar :: bar}


BTW, this is pretty much just the Either type from the prelude.  I'm  
not familiar with the term 'indirect composite' (it sounds like a GoF- 
ism...), but this construction is often called 'disjoint union' in  
the papers I've read.



--- Assume some PFoobar (parsed)
data PFooBar = PF {unPF :: FooBar String String}
--- Assume some TFoobar (typed)
data TFooBar = TF {unTF :: FooBar Int String }

-- Merrily we write our conversion, using binding to optimize  
slightly

typer :: PFooBar -> TFooBar
typer pFooBar =
case unPF pFooBar of
[EMAIL PROTECTED] { unFoo = foo} -> -- We only need to change foo
TF $ f{unFoo = 1}
[EMAIL PROTECTED] { unBar = bar} -> -- We don't need to change this string
TF $ b -- So we just return b



--- Nice little main to make this a full module:
main :: IO ()
main = do
print . typer . PF . Foo $ "Hello"

--- Type error:
-- TypeCast.hs:19:11:
-- Couldn't match `Int' against `String'
-- Expected type: FooBar Int String
-- Inferred type: FooBar String String
-- In the second argument of `($)', namely `b'
-- In a case alternative: ([EMAIL PROTECTED] {unBar = bar}) -> TF $ b

--- what is the fix? Basically do a noop on b
--- [EMAIL PROTECTED] {unBar = bar} ->
--- TF $ b{unBar = bar}


As you noted, the correct way to do this is to destruct the value and  
reconstruct.  It's a little irritating, and it often happens in code  
using Either and similar constructs.


If you rewrite as using Either, and remove a few 'data' wrappers, you  
get:


typer:: Either String String -> Either Int String
typer = either (const (Left 1)) Right

Or:

typer (Left _) = Left 1
typer (Right x) = Right x


Where you can clearly see the destruction/construction pair.  You can  
wrap this up in helper functions, but I don't think there's any real  
way to remove it altogether.  (well, there's always unsafeCoerce#,  
but I can't really recommend you play around with that).  Obviously  
this can become a pretty big pain if you've got more than just a few  
constructors and/or deeply nested datatypes.


If the boilerplate becomes a serious problem, you can investigate one  
of the systems for generic programming in Haskell.  Scrap Your  
Boilerplate, Strafunski and, the GHC -fgenerics option are the ones I  
know of.




Cheers,
Christophe



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG

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


Re: [Haskell-cafe] Problem trying to get class Bounded to work

2006-05-23 Thread Robert Dockins


On May 23, 2006, at 11:13 AM, Jacques Carette wrote:


Bertram Felgenhauer wrote:


Jacques Carette wrote:


Bulat Ziganshin wrote:



malloc :: Storable a => IO (Ptr a)
malloc  = doMalloc undefined
where
 doMalloc   :: Storable b => b -> IO (Ptr b)
 doMalloc dummy  = mallocBytes (sizeOf dummy)




Is there any reason to not code this as

malloc :: Storable a => IO (Ptr a)
malloc  = mallocBytes $ sizeof undefined



What type would the 'undefined' have in this context?

sizeOf has type Storable a => a -> Int -- that doesn't help.

The purpose of doMalloc is to force the type checker to choose
the right type for that 'undefined'.

I still don't quite see it!  To my eyes, the type of doMalloc and  
the type of malloc look exactly "the same", with neither providing  
more specificity than the other.  Also, the 'undefined' can be of  
any type, as long as it is from class Storable.  So it is a  
placeholder for a dictionary - what else does it need?  [Constraint- 
typing-wise, it doesn't need anything else, but perhaps the issue  
is that I don't understand Haskell's type system quite well enough].


I guess I am also asking "Is there a GOOD reason why the simpler  
code can't be used?".  Or maybe what I really need is


malloc :: Storable a => IO (Ptr a)
malloc  = mallocBytes $ sizeof undefined::a

?  That would make sense to me, since in a more general function I  
might have 2 instances (Storable a, Storable b) available, and 2  
undefineds, and I could not know how to match them up  
deterministically in all cases.


I guess I prefer a type annotation over a dummy function that is  
there just to force the type checker to believe me.  If one has to  
force the type checker, may as well do it with a type, not code!



Sure, and there's good reasons to prefer this.  It's not Haskell 98,  
however.  In Haskell 98 type variables in type signatures are not in  
scope in the body of the function.  Adding the type annotation  
(undefined::a) is the same as (undefined::forall a. a) because free  
type variables are automatically bound with universal quantifiers.   
Obviously, that isn't what you want here.  So instead one has to play  
games with the type checker to force the right things to unify.   
Another thing you'll see sometimes is lazy pattern matching and  
'asTypeOf' used to get at type variables inside data types.



GHC has an extension to allow scoped type variables and there's also  
a Haskell' ticket for it.


http://www.haskell.org/ghc/docs/latest/html/users_guide/type- 
extensions.html#scoped-type-variables

http://hackage.haskell.org/trac/haskell-prime/wiki/ScopedTypeVariables




Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


Re: [Haskell-cafe] The values of infinite lists

2006-05-23 Thread Robert Dockins


On May 23, 2006, at 9:50 AM, Paul Hudak wrote:


Hi Claus --

I think that you're asking for a semantics of the entire OS, i.e.  
the entire outside world, and for that I agree that something other  
than equational reasoning is needed to reason about it.  However, I  
would argue that that is outside the mandate of a book on Haskell.   
But maybe that's the point -- i.e. others feel otherwise.


My main point it that if we're reasoning about a single Haskell  
program (with no impure features), then the entire world, with all  
its non-determinism internal to it, can be modelled as a black box  
-- i.e. a function -- that interacts with the single Haskell  
program in a completely sequential, deterministic manner.  And for  
that, equational reasoning is perfectly adequate.


The original Haskell report in fact had an appendix with a  
semantics for I/O written as a Haskell program with a single non- 
deterministic merge operator.  The reason for the non-deterministic  
merge was to account for SEVERAL Haskell programs interacting with  
the OS, but for a single program it can go away.  I claim that such  
a semantics is still possible for Haskell, and equational reasoning  
is sufficient to reason about it.


If you disagree, then please tell me which features in Haskell (a  
particular I/O command, perhaps?) cannot be modelled as a  
function.  I'm not familiar with your thesis, but I note in the  
abstract that you "extend an existing, purely functional language  
with facilities for input/output and modular programming".  If  
those extensions cannot be modelled as pure functions, then I would  
agree that a process calculus (say) would be the right way to go.   
But as far as i know, Haskell doesn't have such features.



IO.hGetContents?  I suspect the result of using hGetContents on a  
file you have open for writing in the same program can't be modeled  
as a pure function; at best you can say it depends on the order of  
evaluation which isn't defined.  Not that it's necessarily a huge  
blow to your argument (hGetContents is viewed with some suspicion  
anyway), but it is a Haskell98 feature.


Things obviously get more complicated in the presence of  
concurrency.  I'm not certain, but I believe some of the memory  
consistency models being discussed for Haskell' are not expressible  
using a non-deterministic merge, which basically assumes that all  
program actions are serializable.


http://www.haskell.org//pipermail/haskell-prime/2006-March/001168.html



  -Paul


Claus Reinke wrote:

Paul Hudak wrote:
As an author of such a book, I'm not willing to do this.  Or at  
least, if we omit concurrency and impure operations such as  
unsafePerformIO, Haskell is a purely functional, sequential, and  
deterministic language, whose semantics, including that of IO,  
can be explained via conventional equational reasoning.
I'm very surprised to hear you say this, and I certainly cannot  
agree.
a language that contains elements that are not best expressed as  
functions

is not "purely functional" anymore, even when its design carefully
ensures that it is still pure, and mainly functional, and can be  
reasoned
about equationally. the element that falls outside the remit of  
functions

is the interaction with the runtime context (operating system/other
processes/users/external world/..).
Haskell's approach to this issue is mostly functional and clearly  
separates functional part from the part that is "out of its  
hands": functionally compute an interaction description, have that  
interaction performed under outside control, have control returned  
to functional evaluation with a representation of the interaction  
result, repeat until done. (an informal recipe like this may be  
even more suitable for

learners than either process calculus rules or claims about being
purely functional in principle).

>
if you wanted to model that middle part functionally, you'd have  
to cover all of the external world as well as scheduling. one nice  
thing about a process calculus style operational semantics is the  
modular description; you only need to model how Haskell programs  
fit into the external world, not the external world itself:  
assuming that world to be modelled in the same style, we need a  
miniscule amount of process calculus rules to describe the i/o  
interactions, falling back to functional-only reasoning for the  
vast majority of the language.
I'm sure that it can also be explained via a suitable process  
calculus, but that is an overkill -- such calculi are best used  
for describing non-deterministic / concurrent languages.
using a process calculus framework does not imply that each  
process has to be non-deterministic / concurrent -- it just makes  
it easier to
show how the "purely functional, sequential and deterministic"  
evaluation inside a process running Haskell is embedded into and  
influenced by interactions with the rest of the framework.

attempts to ignore that extern

Re: [Haskell-cafe] Newbie: Applying Unknown Number Arguments to A Partial Function

2006-05-19 Thread Robert Dockins


On May 19, 2006, at 2:49 PM, Jeremy Shaw wrote:

Hello,

You can do it -- but it may not be very useful in its current
form. The primary problem is, "What is the type of 'f'?"


applyArgument f [arg] = f arg  -- NOTE: I changed (arg) to [arg]
applyArgument f (arg:args) = applyArgument (f arg) args


Looking at the second line, it seems that f is a function that takes a
value and returns a function that takes a value and returns a function
that takes a value, etc. Something like:

f :: a -> (a -> (a -> (a -> ...)))

This is called an 'infinite type' and is not allowed in haskell (or
ocaml by default) because it allows you to introduce type errors that
the compiler can not catch:

http://groups.google.com/group/comp.lang.functional/browse_thread/ 
thread/3646ef7e64124301/2a3a33bfd23a7184


If you introduce a wrapper type, you can make the type checker happy:

newtype F a = F { unF :: a -> F a }

applyArgument :: F a -> [a] -> F a
applyArgument (F f) [arg] = f arg
applyArgument (F f) (arg:args) = applyArgument (f arg) args

Of course, your final result is still something of type 'F a' -- so it
is probably not very useful -- because all you can do is apply it more
more things of type a and get more things of type 'F a'.

One option would be to modify the function to return a result and a
continuation:

newtype F a = F { unF :: a -> (a, F a) }

applyArgument :: F a -> [a] -> a
applyArgument (F f) [arg] = fst (f arg)
applyArgument (F f) (arg:args) = applyArgument (snd (f arg)) args

Then you define a function like this (a simple sum function in this
case):

f :: (Num a) => a -> (a, F a)
f a' = (a', F $ \a -> f (a + a'))

example usage:

*Main> applyArgument (snd (f 0)) [1,2,3]
6



This seems like it is just an ugly way to spell 'foldl'.  Is there  
something fundamentally different about this approach, besides the  
slightly odd typing?  I understand its relation to the OP, but I'm  
just curious now...




Here is another variation that allows for 0 or more arguments instead
of 1 or more:

newtype F a = F { unF :: (a, a -> F a) }

applyArgument :: F a -> [a] -> a
applyArgument (F (result, _)) [] = result
applyArgument (F (_ , f)) (arg:args) = applyArgument (f arg) args

f :: (Num a) => a -> F a
f a' = F (a', \a -> f (a + a'))

j.



At Fri, 19 May 2006 02:25:31 +,
Aditya Siram wrote:


I am trying to write a function 'applyArguments' which takes a  
function and
a list and recursively uses element each in the list as an  
argument to the
function. I want to do this for any function taking any number of  
arguments.


applyArgument f (arg) = f arg
applyArgument f (arg:args) = applyArgument (f arg) args

This has failed in Hugs, so my question is: Can I conceptually do  
this? If

so, what is the type signature of this function?

Deech




Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG



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


[Haskell-cafe] Haskell DB and XML libs: one user's experience

2006-05-16 Thread Robert Dockins

Hello all,


I recently found myself needing to do some data manipulation; I  
needed to take some data from a database and generate a series of XML  
files from it.  In the past I've done most of this sort of work in  
Java, but this time I decided I'd take the opportunity to explore the  
state of the art of Haskell DB and XML libraries.



As to DB, I tried using HDBC first.  I was actually a little  
surprised how straightforward it was.  My database (PostgreSQL) is  
directly supported, and the compile/install went smoothly.  My first  
test connection program that typechecked worked as expected (!) and I  
was soon executing queries doing useful work with the results.  I'd  
just like to take a moment to congratulate John Goerzen for creating  
a product with a low barrier of entry for using databases in  
Haskell.  As I didn't really do anything beyond simple queries, can't  
comment on more advanced features.



For XML, I wavered between HaXml and HXT (the Haskell XML Tookbox).   
I initially decided to use HXT because it has support for xml  
namespaces, which I was going to need, and because it just seems to  
be the most complete and advanced package available.  The HXT install  
suffers a little bit from transitive-closureitis, but, overall wasn't  
too bad.  However, I had a really hard time using it!  The API is  
_really_ intimidating, and I couldn't find any basic tutorial-style  
documentation.  The API docs are a little hard to use because related  
definitions are spread out over a bunch of modules, and the links  
don't always work.  Also, the theses are nice, but they read like  
theses ;-)  That's not what I want when I have a job to complete.   
Long story made short; I couldn't figure out how to create and XML  
document and serialize it to disk.  I was reasonably motivated and  
I'm a pretty experienced Haskell programmer, but I had to call it  
quits after about 3 hours of struggling with it.  Most of my programs  
would mysteriously fail to produce output OR errors!  It was really  
frustrating.



I ended up using HaXml instead and shoehorning in the namespaces by  
using attributes named "xmlns:xyz" etc. on the document root element  
(which is OK, but not ideal).  The HaXml API was also tough to work  
with but was less mystifying than HXT's, and I eventually got it to  
work.  I was a little disappointed by the results, because the pretty  
printer does some fairly bizarre things to ensure that it doesn't  
introduce extra whitespace into the DOM.  I also had to do some  
futzing to make HaXml correctly escape literal text.  Finally, the  
using the HaXml API to generate XML results in verbose code that's  
hard to read.  I was hoping that I'd get results comparable to using  
xmlenc (http://xmlenc.sourceforge.net/) in Java, but I was  
disappointed by fairly low signal-to-noise ratio (although in all  
fairness, its probably comparable to using the DOM or SAX Java  
APIs).  Overall, HaXml works, but feels a bit awkward, at least for  
this use case.



Now taking a slightly closer look at HXML, I see that it may be the  
best choice for what I was attempting to do (although it also doesn't  
support namespaces).  The simplified representation looks  
particularly nice for building XML from scratch.  I may try rewriting  
with HXML and see how that goes.



So that's it.  I don't have any deep conclusions, but I thought I'd  
share my experiences in the hopes that they will be helpful to somebody.




Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG

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


Re: [Haskell-cafe] Newbie:Debugging and Overgeneralization

2006-05-15 Thread Robert Dockins


On May 15, 2006, at 11:14 AM, Aditya Siram wrote:

I have been working with a Haskell text for the past couple of  
months or so and I have some general problem solving questions.


1. Is there a way to output intermediate values of a calculation?  
As an imperative programmer I have become used to using  
"System.out"'s or 'cout's to check that my function works as  
intended. I can see no easy way to do that in Haskell. The only  
solution I could come up with was to avoid using nested functions  
except for the most trivial expressions and test all expressions in  
the interpreter. This approach seems to make my code ugly and less  
readable.


Two responses here:

1) Check out Debug.Trace in the standard libs.  (http:// 
www.haskell.org/ghc/docs/latest/html/libraries/base/Debug- 
Trace.html)  It lets you insert debugging messages into pure code.   
Be warned, its a little tricky to use; your message will only be  
printed _when_and_if_ the thing you "attach" the message to is  
evaluated.


2) I'm not sure exactly what you mean by "nested functions", but  
writing small functions and composing them together to do larger  
tasks is a pretty Haskellish way to approach things.  As you noted,  
this lets you easily test subparts of your computation, and it's  
generally considered good style.  Appropriate use of the composition  
operator (.) or of monads can make function composition more readable.


Creating intermediate representations and writing functions that  
transform data between these representations is a good way to  
structure programs that allows this compositional style.  See: http:// 
www.haskell.org/hawiki/IntermediateRepresentation


2. Haskell is great because it makes abstracting from problem very  
easy. For example, if the problem asks for the area of a square,  
why not write a function to compute the area of all polygons?  find  
myself falling into the trap of generalizing to the point that a  
simple problem becomes quite a bit harder . From a general design  
perspective should I concentrate on abstracting away just enough to  
solve the problem or solve the harder problem in the hoping of  
reusing that code to make life easier in the future?


I'd say, unless you are developing a general-purpose library, solve  
the problem in the simplest (correct!) way first.  One of the nice  
things about Haskell is that its easy to replace code under the hood  
at a later time (pure functional programming is your friend).



For example if you write:

> areaOfSquare :: Square -> Double
> areaOfSquare = 


And later you discover you also need:

> areaOfNPolygon :: NPolygon -> Double
> areaOfNPolygon = 


You can replace areaOfSquare with:

> areaOfSquare = areaOfNPolygon . squareToNPolygon


to reduce duplication, or you can keep the special-purpose code in  
the interests of efficiency.  If you keep the special-purpose code,  
you can use quick check to make sure it gives the same answer as the  
n-polygon routine, which is a nice benefit.




Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG

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


Re: [Haskell-cafe] CDouble type coercion

2006-05-14 Thread Robert Dockins
On Sunday 14 May 2006 03:00 pm, SevenThunders wrote:
> Thanks that helps a bit.  The realToFrac type coercion works, but
> ultimately it seems
> that printf won't play nice.  Consider this simple haskell code
>
> module Test
>   where
> import IO
> -- import Data.Array.Storable
> import Text.Printf
> import Foreign.C.Types (CInt, CDouble )
>
> y :: CDouble
> y = 5.2
> u = realToFrac(y)
> test = do  printf "%14.7g" u

Try:

y :: CDouble
y = 5.2
u :: Double
u = realToFrac(y)
test = do  printf "%14.7g" u

The root problem seems to be that GHC isn't sure what type 'u' has unless you 
fix it with a type signature because 'realToFrac' has a polymorphic type.  
I'm not sure why it works when you type it at the interpreter.


> Compiling it into GHCi I get the error,
> test.hs:13:11:
> No instance for (PrintfType (t t1))
>   arising from use of `printf' at test.hs:13:11-16
> Probable fix: add an instance declaration for (PrintfType (t t1))
> In the result of a 'do' expression: printf "%14.7g" u
> In the definition of `test': test = do printf "%14.7g" u
> Failed, modules loaded: none.
>
> If I replace the printf by a standard print there is no problem.  Also if I
> comment out
> the line with test = ... , it will load (compile) and I can then type in
> the interpreter
> printf "%14.7g" u
> and it works!
>
> but
> printf "%14.7g" y
>
> fails because y is of type CDouble.  At this point I think I'm giving up on
> the
> formatted printing in Haskell.  It's just too persnickety.
> I guess I'll just call printf via C and see what happens.
>
> --
> View this message in context:
> http://www.nabble.com/CDouble-type-coercion-t1615450.html#a4383006 Sent
> from the Haskell - Haskell-Cafe forum at Nabble.com.
>
> ___
> Haskell-Cafe mailing list
> Haskell-Cafe@haskell.org
> http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] The values of infinite lists

2006-05-10 Thread Robert Dockins
On Wednesday 10 May 2006 02:49 pm, you wrote:
> Robert Dockins wrote:
> > On Wednesday 10 May 2006 12:30 pm, Brian Hulley wrote:
> >> Bjorn Lisper wrote:
> >>> Nontermination is not
> >>> the precisely the same as _|_. Only certain kinds of nontermination
> >>> can be modeled by _|_ in a non-strict language.
> >>
> >> What kinds of non-termination are *not* modelled by _|_ in Haskell?
> >
> > Non-termination that is "doing something".
> >
> > For example consider:
> >
> > ] ones = 1 : ones
> >
> > If I try to take its length, I get _|_.  So:
> >
> > ] main = print (length ones)
> >
> > Will churn my CPU forever without producing any output.
> >
> > However, if I print each item sequentially:
> >
> > ] main = mapM print ones
> >
> > I'll get a never-ending stream of '1' on my console.  This is not the
> > same as bottom because it's "doing something".
>
> I can see what you're getting at, but I don't know if I agree with the idea
> that "doing" should affect whether or not one sees the result of the above
> computation as bottom or not. With a hypothetical implementation of
>
>   runIO :: IO a -> RealWorld -> (RealWorld, a)
>
> I could write:
>
> ] (r',_) = runIO (mapM print ones) realWorld
>
> and this computation, even though some printing would be observable, still
> evaluates to bottom, because r' will never be bound.

Humm... how do you define observable? If r' is never bound, how can I observe 
any intermediate printing?

More generally, if you want the possibility of implementing 'runIO' as a pure 
function (the world-state-transformer view of Haskell IO), you are forced to 
make a closed-world assumption.

I don't believe that concurrency can be given a nice story in this view;you 
pretty much have to do something ugly like calculate the result of all 
possible interleavings (yuck!).  And your world is still closed.

The world-state-transformer idea is nice as a didactic tool, but I don't think 
its the right world-view for serious thinking about Haskell's semantics.

> > Now, obviously this definition is pretty imprecise, but maybe it
> > helps you get the idea.  Now for the corner cases.  What about:
> >
> > ] main = sequence_ repeat (return ())
> >
> > ?  I'd personally say it is _not_ bottom.  Even though "return ()" is
> > a completely useless action, I'm inclined to say its "doing
> > something" in some theoretical sense (mostly because I think of _|_
> > as being a property of the functional part of Haskell).
>
> I thought everything in Haskell is purely functional - surely that is the
> whole point of using monads? :-)

Sure.  But in that world-view then you don't think of the IO actions as 
"running" at all, so you can't discuss their termination properties.  This is 
more or less what all accounts (at least the ones I've seen) of Haskell's 
semantics do -- they provide a denotational semantics for the lambda terms 
basicaly ignore the meaning of IO actions.

> I'd have thought that "doing" is simply a  projection of the purely
> functional "being" into the stream of time and therefore cannot be part of
> the discourse regarding the nature of bottom...

My favorite view of Haskell semantics is of a coroutining abstract machine 
which alternates between evaluating lambda terms to obtain the terms of a 
process calculus, and then reducing those process calculus terms; some 
process calculus reduction rules call into the lambda reduction engine to 
grow more (process calculus) terms to reduce.  The observable behavior of the 
program is defined in terms of the sequence of reductions undertaken by the 
process calculus engine.

In this view "bottom" is the denotion of all (lambda) terms which make the 
lambda portion of the machine fail to terminate, and never return control to 
the process calculus part -- thus no further observations will be generated 
by the program.

> Regards, Brian.



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


Re: [Haskell-cafe] The values of infinite lists

2006-05-10 Thread Robert Dockins
On Wednesday 10 May 2006 12:30 pm, Brian Hulley wrote:
> Bjorn Lisper wrote:
> > Nontermination is not
> > the precisely the same as _|_. Only certain kinds of nontermination
> > can be modeled by _|_ in a non-strict language.
>
> What kinds of non-termination are *not* modelled by _|_ in Haskell?

Non-termination that is "doing something".

For example consider:

] ones = 1 : ones

If I try to take its length, I get _|_.  So:

] main = print (length ones)

Will churn my CPU forever without producing any output.

However, if I print each item sequentially:

] main = mapM print ones

I'll get a never-ending stream of '1' on my console.  This is not the same as 
bottom because it's "doing something".

Now, obviously this definition is pretty imprecise, but maybe it helps you get 
the idea.  Now for the corner cases.  What about:

] main = sequence_ repeat (return ())

?  I'd personally say it is _not_ bottom.  Even though "return ()" is a 
completely useless action, I'm inclined to say its "doing something" in some 
theoretical sense (mostly because I think of _|_ as being a property of the 
functional part of Haskell).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: [Haskell] FP-style vs. OO-style AST structure

2006-05-10 Thread Robert Dockins
[moved to haskell-cafe]

On Wednesday 10 May 2006 11:09 am, Doug Kirk wrote:
> Hi,
>
> I'm a Haskell newbie, but not new to programming, and I have a
> question regarding style (I think).
>
> I'm writing a parser for OMG's OCL, and have two ways of defining the
> AST model of a constraint. Each constraint in OCL has the following 4
> characteristics:
>
> 1. name :: Maybe String
> 2. context :: UmlElement
> 3. expr :: OclExpression
> 4. type :: OclConstraintType
>
> Now, having come from an O-O background, this looks right; however, in
> an FPL, it may not be. OclConstraintType is essentially an enumeration
> of the values:
>
>  Invariant
>
>| Precondition
>| Postcondition
>| InitialValue
>| Derivation
>| Body
>
> The question is this: is it better to create a single type as above
> with a 'type' attribute, or would it be better to use the types as
> separate constructors of a Constraint, each constructor taking the
> same attributes?

Opinions may differ on this, bit I'm going to go out on a limb and say that 
using separate constructors with the same field names is the more idiomatic 
approach in Haskell.

Having a product type or a big record with an enumerated tag field is usually 
just a way to simulate sum types.  Why do that if the language supports them 
directly?

> I'm looking to avoid any pitfalls that could occur with either
> decision, and at this point I don't know the benefits of doing it one
> way vs. the other.

So long as every constraint has exactly the same fields, there isn't much 
practical difference.  If later you discover that different kinds of 
constraints need different fields, you'll be better off with the separate 
constructors.

> BTW, I am using UUST Parser Combinator AG for the parser definition,
> in case that makes a difference.
>
> Thanks!
> --doug
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Current situation regarding global IORefs

2006-04-24 Thread Robert Dockins


On Apr 24, 2006, at 2:42 AM, Adrian Hey wrote:

Lennart Augustsson wrote:

I think global mutable variables should be regarded with utmost
suspicion.  There are very few situations where they are the
right solution.


Well IMO even the use of the term "global mutable variable" causes
muddled thinking on this and I wish people would stop it. There's no
reason to regard top level "things with identity" (call them "TWI"s
or "objects" or whatever) with any more suspicion than top level IO
actions themselves.


Sure there is.  TWI's are just the object-oriented singleton pattern  
warmed over, and the singleton pattern is much maligned in some  
circles (for good reason, IMO).



One thing I never could fathom about the position of the nay-sayers
in this debate is what exactly is it that they object to?
Is it existence of top level "TWI"s and of IO operations that
reference them *in principle*?
Or are they content with their existence but just don't want to
allow people to use Haskell to define them?


The former, in my case.  As I stated in an earlier message, the  
problem is primarily one of defining the dynamic scope of the thing.   
If you look back in the archives, you'll notice I proposed a thread- 
local state mechanism because I felt it placed the scope boundary in  
an appropriate place, where it could be manipulated and reasoned  
about by programmers, and where it has a reasonable semantic  
interpretation.  Presumably, runtime models will have to deal somehow  
with the notion of a thread of execution (even if just to say there  
is only ever one) and will thus fix the dynamic scope of thread local  
state.


I additionally think that thread-local state (and similar mechanisms)  
can be abused to create difficult-to-maintain and buggy code, but  
that's a somewhat separate issue.



If it's the former then we should be purging the IO libraries of
all such horrors, though I can't see much remaining of them (well
anything actually). But I guess an IO incapable language might
still have some niche uses.


Argument by straw-man: there are important differences between  
regular IO actions and TWI's, AKA singletons.  The former is  
referentially transparent, while the latter is referentially opaque,  
for starters.  There's also the scoping issue: the properties of the  
IO monad bound the dynamic scope of regular IO actions, but not so  
for singletons.



If it's the latter then we are advocating a language which cannot
be used to implement many demonstrably useful IO modules and  
libraries,

*by design*. If so, the claim that Haskell is a general purpose
programming language seems quite bogus and should be removed from
the haskell.org home page IMO.


You presuppose that a language which "cannot be used to implement  
many demonstrably useful IO modules and libraries" is not general  
purpose.  I claim that is silly.  If we take that argument to its  
logical conclusion, then we should throw out static typing,  
referential transparency and most of the things that make Haskell  
what it is.  I think that what a programming language keeps you from  
doing is as least as important as what it lets you do.  If you don't  
believe that at least to some extent, then your first exposure to  
Haskell probably made your head explode.


That said, I also disagree with the premise.  I don't know of any  
stateful library designs that can't be pretty straightforwardly  
refactored using explicit initialization and ReaderT-over-IO monads.   
Furthermore, I believe that a library so structured is actually  
_more_ useful than the library with implicit state.



Regards
--
Adrian Hey



Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG


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


  1   2   3   >