Re: [Haskell] Re: Implicit parameters redux

2004-01-29 Thread Ben Rudiak-Gould
On Thu, 29 Jan 2004, Ashley Yakeley wrote:

>  Ben Rudiak-Gould <[EMAIL PROTECTED]> wrote:
> 
> > Another extension I proposed is that the "name" of an implicit return
> > value can include type parameters: thus %foo Int and %foo Char would be
> > treated as though they had different names.
> 
> This bit doesn't seem very polymorphic-friendly?

Well, there can be type variables there too.

The issue is that there needs to be a source of fresh names for
newly-created state threads, and the simplest solution I could think of
was to return an existentially-quantified %foo s. It's supposed to work
along the lines of a (Num a, Num b) context, where the type checker
doesn't merge the constraints because it can't prove they're equal, even
though it also can't prove they aren't. It's not clear that it's formally
sound, though.

Also, it would be nice if the type-class system could be implemented in
terms of implicit parameters (plus sugar), and this extension would help
with that.

It might be possible to just parameterize the type of the implicit
parameter instead of its name, and decree that merging happens by name and
type.

-- Ben

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


Re: [Haskell] Re: Compiling HXML toolbox under Hugs/Windows

2004-01-29 Thread Ferenc Wagner
Graham Klyne <[EMAIL PROTECTED]> writes:

> Well, further to my previous response, it appears that
> there's a problem with GHC as well...  The XmlInput module
> imports a module called MD5, and uses a maethod 'digest'
> from that module.  I cannot find a copy of that module
> either in the HXML toolbox distribution, or in the GHC
> distribution.  I did find this in the GHC 6.2 release
> notes:
>
> [[
> The MD5 library in the util package has been removed. We'll include a
> replacement in the hierarchical libraries if someone would like to
> send us one!
> ]]
>
> Is your software tested under GHC 6.2?

The software is not mine, but I committed the following hack
to have it compile:

h x = MD5.md5s (MD5.Str x)
{- h = IOExts.unsafePerformIO . MD5.digest -}

ie. commented out the second line instead of the first.  I
don't care about authentication, so I don't know if it
actually works...

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


[Haskell] ANNOUNCE: HaRe, the Haskell Refactorer, version 0.2; and a workshop

2004-01-29 Thread C.Reinke

Dear Haskellers,

as part of our project on Refactoring Functional Programs

  http://www.cs.kent.ac.uk/projects/refactor-fp/

we are pleased to announce the availability of HaRe 0.2 (also known
as HaRe 27/01/2004 ;-), a snapshot of our Haskell Refactorer
prototype. The major changes since HaRe 0.1 (apart from numerous
bug-fixes, a clean-up of the Emacs binding, and initial support for
literate Haskell files) are that all refactorings are now
module-aware and can thus be used in multi-module settings. 

You can get HaRe 0.2 via

  http://www.cs.kent.ac.uk/projects/refactor-fp/hare.html

Please see the README.txt for build/use instructions and known
issues, and let us know about any problems, bugs, suggestions, or
additional platforms you can confirm as working: our project address
at kent.ac.uk is refactor-fp.

The catalogue describing the refactorings implemented in HaRe
has been updated and is included in the doc/ directory.

This means that our basic platform is now fairly complete
(type-awareness is the next big step), and that in future we can
hopefully focus a bit more on extending the range of refactorings,
and the range of our collaborations. 

To this end, we are organising a one-day workshop here in
Canterbury, on Monday, 09 February 2004:

  http://www.cs.kent.ac.uk/projects/refactor-fp/workshop.html

If you'd be interested in participating, please let us know.


Happy Refactoring!

  The HaRe Team (Huiqing Li, Claus Reinke, Simon Thompson)

  project email: refactor-fp (at kent.ac.uk)


--

Background: 

  Refactoring is the process of changing the structure of programs
  without changing their functionality, i.e., refactorings are
  meaning-preserving program transformations that implement design
  changes. For more details about refactoring, about our project and
  for background on HaRe, see our project pages and the
  papers/presentations/catalogue/demo/etc. available there, especially
  our contribution to last year's Haskell Workshop.

HaRe - the Haskell Refactorer:

  HaRe is our prototype tool supporting a first few basic refactorings
  for Haskell 98 (see README.txt for known issues and limitations).

  It is implemented as a separate refactoring engine (on top of
  Programatica's Haskell frontend and Strafunski's generic traversal
  strategy library), with small scripting frontends that call this
  engine from either Vim or Emacs. The refactoring engine itself has
  been seen to build (with ghc-6.0.1) and run on most flavours of
  Windows (cygwin needed to build) and on Suns (binutils recommended
  to build), so we expect it to build and work on other unix-like
  platforms with almost no changes.  

  In other words, we've tried to make sure that most of you should be
  able to build and use HaRe from your favourite OS/editor. 

  Currently supported refactorings: 

 removeDef  : remove an unused definition
 duplicateDef   : duplicate a definition under a new name

 liftToTopLevel : move a local definition to top level
 liftOneLevel   : move a local definition one level up
 demote : move a definition local to point of use

 rename : rename an identifier
 introNewDef: turn expression into use of new definition
 unfoldDef  : replace use of identifier by right-hand side

 addOneParameter: add parameter to definition
 rmOneParameter : remove unused parameter from definition
 generaliseDef  : turn expression on rhs of definition into 
  new parameter of that definition

  A series of screenshots illustrating some of the tasks one might
  want to accomplish with these refactorings can be found via the 
  HaRe page (see above for URL).

Caveats (see also README.txt):

  Please keep in mind that this is a prototype, so we do not recommend
  to use it on your productions sources just yet. Just play with it
  to get an idea of tool-supported refactoring in Haskell, and send us
  your feedback and bug-reports. Our goal is to develop this into a
  tool that many of you will find indispensible for Haskell
  development, and while we won't be able to follow every suggestion,
  we've got about 1.5 more years in which to work towards this goal!-)

History:

  Functionally, HaRe 0.1 was still roughly the snapshot you'd seen at 
  the Haskell workshop, packaged up for relative ease of build/use,
  but unaware of types and modules, and all refactorings only working 
  on a single module. It had some annoying issues that plagued some 
  of our Emacs users, didn't work at all with literate Haskell
  files, and had several other minor problems.

  HaRe 0.2 has not added refactorings, but all refactorings have
  now been modified to take Haskell's module system into account.
  This means that a single refactoring may affect multiple modules
  in a given project (e.g., renaming an exported function should
  trigger corresponding renamings in all clie

Re: [Haskell] new "primitive" instances of Data?

2004-01-29 Thread Ralf Laemmel


I'm in the process of trying to write generic binary serialization code
using the "Scrap Your Boilerplate" method.  One bump I've run into is that
there are no instances of Data provided for the extended set of numeric
types (the stuff in Data.Word, etc.) and it seems to be impossible to
hand-write an instance that behaves similarly to the instances for other
primitive types.  Any ideas for ways around this?
 

Hi,

as a basis for disucssion I propose bit serialisation as in:
http://www.cs.vu.nl/boilerplate/testsuite/bits/Main.hs
alternatively, the inner workings of normal read and show are inspiring too:
http://www.cs.vu.nl/boilerplate/library/Text.hs
Your problem seems to refer to instances like the following:
(Data.Generics.Basic)
-- Another basic datatype instance
instance Data Integer where
 toConstr x = IntegerConstr x
 fromConstr (IntegerConstr x) = x
 dataTypeOf _ = IntegerType
This GHC 6.2 library instance indeed relies on a CWA
as far as basic datatypes are conveniently supported.
This is your problem, isn't it.
Let me also show the CWA datatype here for convenience:

-- | Representation of constructors
data Constr =
-- The prime case for proper datatype constructors
   DataConstr ConIndex String Fixity
-- Provision for built-in types
| IntConstr Int
| IntegerConstr Integer
| FloatConstr   Float
| CharConstrChar
-- Provision for any type that can be read/shown as string
| StringConstr  String
-- Provision for function types
| FunConstr
 deriving (Show, Typeable)

This CWA is there because it allows us to map types to constructors
and to go back without inefficient or imprecise conversion. It is basically
there for an optimisation. It can be bypassed without problems.
That is, there seem to be two ways to handle the problem you have:

a) Go via read and show for all the various types such as in:
(from Data.Generics.Basics again)
-- A basic datatype without a specific branch in Constr
instance Data Rational where
 toConstr x = StringConstr (show x)
 fromConstr (StringConstr x) = read x
 dataTypeOf _ = StringType
(You can also use other functions that show and read of course.)

b) Use type extension via mk? and ext? combinators as in generic read:
(from Data.Generics.Text again)
gread = readP_to_S gread'

where

 gread' :: Data a => ReadP a
 gread' = gdefault `extR` scase
  where

   -- A specific case for strings
   scase :: ReadP String
   scase = readS_to_P reads
   -- The generic default for gread
   -- gdefault :: Data a => ReadP a
   gdefault = ...
Please let me know if you need further help.
Simon PJ and I have a draft which explains all this
but it is too clumsy to release yet :-)
All the best,
Ralf
--
Ralf Laemmel
VU & CWI, Amsterdam, The Netherlands
http://www.cs.vu.nl/~ralf/
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] new "primitive" instances of Data?

2004-01-29 Thread Abraham Egnor
I'm in the process of trying to write generic binary serialization code
using the "Scrap Your Boilerplate" method.  One bump I've run into is that
there are no instances of Data provided for the extended set of numeric
types (the stuff in Data.Word, etc.) and it seems to be impossible to
hand-write an instance that behaves similarly to the instances for other
primitive types.  Any ideas for ways around this?

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


Re: [Haskell] Re: Weaving the Web with Haskell

2004-01-29 Thread Graham Klyne
At 19:23 28/01/04 +0100, Ferenc Wagner wrote:
Graham Klyne <[EMAIL PROTECTED]> writes:

> I have been trying to use the HXML toolbox, because I
> understand it's the only XML parser for Haskell that
> supports XML namespaces.  Unfortunately, it seems to be
> rather dependent on older versions of GHC (unless I'm
> missing something), which is making it more problematic to
> adopt than I had hoped.
I may misunderstand you, but I successfully compiled the
HXML Toolbox 3.01 with GHC-6.2 on Linux.
You understood me well.

It did need some
tweaking, but nothing serious: if my memory serves me right
the forkProcess function changed and the MD5 library was
missing.
It's the "tweaking" that bogs me down... and in this case, it was the 
missing MD5 library that was holding me up (though I have since found a 
version of HTTP and compatible MD5 modules).  I don't have time to dig into 
the inner workings of all the code I wish to use.  I hope my comments come 
over as constructive rather than whingeing, but it seems that there are 
some configuration management difficulties with interdependent library 
code.  I hope the library infrastructure project will help here, by 
providing a uniform structure into which modules can be slotted (and 
version-managed).

  I understand that you have a POpen replacement for
Windows, so the rest should be easy...
Well, for some value of "easy" ;-)  I do now have a version of HXML Toolbox 
3.01 that compiles the HUnitExample module using Hugs under Windows, and 
passes most (all but about 10) of the test cases.

#g


Graham Klyne
For email:
http://www.ninebynine.org/#Contact
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] Re: Implicit parameters redux

2004-01-29 Thread Ashley Yakeley
In article <[EMAIL PROTECTED]>,
 Ben Rudiak-Gould <[EMAIL PROTECTED]> wrote:

> Another extension I proposed is that the "name" of an implicit return
> value can include type parameters: thus %foo Int and %foo Char would be
> treated as though they had different names.

This bit doesn't seem very polymorphic-friendly?

-- 
Ashley Yakeley, Seattle WA

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


Re: [Haskell] Implicit parameters redux

2004-01-29 Thread Ben Rudiak-Gould
Here's an example of implicit return values from a project I worked on
recently, followed by an example of the thread idea.

Suppose I've written a decompiler -- it takes binary object code and
produces an abstract syntax tree representing source code. A very
simplified version of the output type might be

  type StatementBlock = [Expr]

  data Expr
= Arith Expr String Expr-- e.g. Arith (Literal 5) "+" (Literal 8)
| Assign Expr Expr
| ProcCall Expr [Expr]
| Literal Int
| TheProcedure Int
| ...

The Int field of "TheProcedure" is the raw address of the beginning of the
procedure in the file. So code like "foo(1,2,3)" will be represented as
something like "ProcCall (TheProcedure 51034) [Literal 1, ...]"

I want to produce source code as output, so I write a function with type
StatementBlock -> String:

  showStatement exprs = concat [ showExpr x ++ ";\n" | x <- exprs ]

  showExpr (Arith left op right) =
showExpr left ++ op ++ showExpr right

  showExpr (ProcCall proc args) =
showExpr proc ++ "(" ++ join "," (map showExpr args) ++ ")"

  showExpr (Literal n) = show n

  showExpr (TheProcedure addr) = "procedure" ++ show addr

The last line leaves something to be desired -- it chooses very unfriendly
names for the procedures. As a matter of fact I have various heuristics
for choosing more helpful names for procedures, and I also allow the user
to supply a configuration file with names. So I encapsulate all this in a
table of names and pass it to showExpr, and I get code like

  showExpr names (TheProcedure addr) =
lookupProcedureName names addr

But the rest of showExpr and showStatement get needlessly ugly, because
they have to pass a "names" parameter to every recursive call. This is
where ordinary implicit parameters become useful. I replace "names" with
"?names" and it gets passed around for me.

Now the decompiler may produce code which refers to procedures I don't
"know about" (haven't decompiled). I can indicate this in the source code
I produce:

  showExpr names (TheProcedure addr) =
case lookupProcedureName names addr of
  Just name -> name
  Nothing   -> "(*** unknown procedure ***)"

But I'd like to also collect these for later use -- say, to list as part
of a summary printed at the end.

There are various ways I could do this, but let me concentrate on this
one:

  showExpr (TheProcedure addr) =
case lookupProcedureName ?names addr of
  Just name -> (name, [])
  Nothing   -> ("(*** unknown procedure ***)", [addr])

  showExpr (Literal n) = (show n, [])

  showExpr (Arith left op right) =
(x++op++y, p++q)
where (x,p) = showExpr left
  (y,q) = showExpr right

This strategy lets us collect a list of unrecognized addresses at the top,
as a second return value. But the code gets very ugly -- much worse than
the implicit parameter case, in fact, since Haskell doesn't have a
convenient notation for multiple return values. I could hide this with a
modified ++ operator:

  (x,p) <++> (y,q) = (x++y, p++q)

Then I could write:

  showExpr (Arith left op right) =
showExpr left <++> (op, []) <++> showExpr right

Better, but not great.

Implicit return values provide a much cleaner solution: just write

  showExpr (TheProcedure addr) =
case lookupProcedureName ?names addr of
  Just name -> name
  Nothing   -> ("(*** unknown procedure ***)", %unknown = [addr])

and you're done. None of the other cases need to be modified (unless they
also produce unknown addresses).

This need to produce some form of statistical information "on the side"
comes up fairly frequently in my code.


Now state threading. Consider the following silly imperative program in C:

  char name[100];
  int i;

  puts("What is your name?");
  gets(name);
  for (i = 0; name[i]; ++i)
name[i] = toupper(name[i]);
  puts("Your name in uppercase is:");
  puts(name);

There's all kinds of mutation and I/O going on here. In imperative
programming there's a "current state", which includes things like the
screen and the keyboard buffer and the array "name", and you give a list
of commands which do something to that state, in a particular order.

A pure functional language doesn't have any implicit state. You can model
state by passing around a state variable, e.g.

  main :: World -> World

  main theWorld =
let theWorld' = puts theWorld "What is your name?"
(name,theWorld'') = gets theWorld'
...
in theWorld'''

This isn't very convenient. Worse, theWorld can't really represent the
world, because you can reuse old values, and that isn't possible in
reality.

We can solve both problems by abstracting away from the world-passing. We
think of puts and gets and similar functions as world-transformers, and we
allow the programmer to attach the output of one to the input of another.
This is the IO monad model. There's no way to duplicate the world because
there's no transformer with one input and two outputs. (Well, there is