Re: [Haskell] Implicit Parameters

2006-02-27 Thread Robert Dockins


On Feb 27, 2006, at 3:31 PM, Ashley Yakeley wrote:


Ben Rudiak-Gould wrote:
I'd advise against using implicit parameters, because (as you've  
seen) it's hard to reason about when they'll get passed to functions.


And Johannes Waldmann wrote:
 Implicit parameters are *evil*. They seem to simplify programs
 but they make reasoning about them much harder.

Feh. Implicit parameters are often exactly what you want. You just  
have to make sure to provide type signatures (-Wall -Werror can  
help here).


In fact it would be useful to allow implicit parameters and other  
type context at the top level of a module:


  forall m. (Monad m,?getCPUTime :: m Integer) = module MyModule  
where

timeFunction :: forall a. m a - m (Integer,a)
timeFunction ma = do
  t0 - ?getCPUTime
  a - ma
  t1 - ?getCPUTime
  return (t1 - t0,a)

This is just syntactic sugar that gives this:

  timeFunction :: forall m a. (Monad m,?getCPUTime :: m Integer) =
 m a - m (Integer,a)

In a future Haskell Operating System, this is how system functions  
could be provided to application code. This would make secure  
sandboxes easy to set up, for instance.


That's pretty similar in spirit to the Sections mechanism available  
in Coq.  (http://coq.inria.fr/doc/Reference-Manual004.html#toc13)


Basically, it lets you declare a lexical region where all definitions  
can assume certain variables are in scope with particular types.   
Outside the section, the definitions are generalized, so that the  
definitions in the section are extended with additional lambdas.  I  
can make complicated type signatures a lot shorter, easier to  
understand and more robust against changes.


Has something like this ever been discussed as a possible Haskell  
language feature?



Rob Dockins

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



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


Re: [Haskell] implicit parameters and the paper prepose.pdf

2004-11-20 Thread Dylan Thurston
On Sat, Nov 20, 2004 at 09:26:08AM -0800, John Velman wrote:
 In a recent message to this list (msg15410) Oleg referenced a paper
 comparing implicit parameters and implicit configurations with url
 http://www.eecs.harvard.edu/~ccshan/prepose/prepose.pdf .  I'd like to read
 this, (and examine the companion literate haskell file prepose.lhs), but
 www.eecs.harvard.edu rejects my connection.  Nor can I find it anywhere
 else.
 
 Is this paper still available somewhere, or is it possible for someone to
 send me a copy?

There was a cracker that broke in to eecs.harvard.edu, so they took the
web server down temporarily till they find and fix the hole.  Meanwhile
you can get it from
http://donkeykong.eecs.harvard.edu/~ccshan/prepose/prepose.pdf

Peace,
Dylan


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


Re: [Haskell] implicit parameters and the paper prepose.pdf

2004-11-20 Thread John Velman
Thanks to everyone who answered!  I now have a copy.

Best to all,

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


Re: [Haskell] Implicit parameters

2004-06-09 Thread Iavor S. Diatchki
hi,
i don't think this is a bug, and this is a situation where it matters
if you use ($) or parens.  the same probelm occurs when you work
with polymorohism, rank-2 and above, e.g. when you use runST.
the problem occurs because ($) has a monomorphic (non-overloaded)
type: 
($) :: (a - b) - (a - b)
now consider the type of runST (same example applies to your problem 
bellow, but with constraints)
runST :: (forall s. ST s b) - b

now if we were to apply ($) to runST, we must make sure that
the type of runST is at least as polymorphic as what is required by ($),i.e.
(forall s. ST s b) - b = a - b
(type on the left should be _more_ polymorphic, i.e. has _less_ elements 
hence the notation)
the above would be true, if
1. b = b  (which is ok)
2. a = forall s. ST s b  (which is not ok, as a is an arbitry 
_monomorphic_ type, and is not more polymorphic then a schema)

hope this helps, for details on the polymorphism  subtyping you may 
take a look at a number of papers
over the past few years.  there are some on simon pj's page i forget the 
exact title, but it is easy to find.

-iavor



Per Larsson wrote:
When using implicit parameters I have noticed (at least for me) a rather 
puzzling behaviour with GHC and Hugs.

Given the declarations
data Env = Env {numlines :: Int, numcols  :: Int}
initEnv = Env {numlines = 0, numcols = 1}
withEnv :: ((?env :: Env) = IO a) - IO a
withEnv io = let ?env = initEnv in io
I can write code like:
main = withEnv (do
 let lines = numlines ?env
 putStrLn (Initial number of lines is  ++ (show lines)))
which works as expected, but the version below
main = withEnv $ do
 let lines = numlines ?env
 putStrLn (Initial number of lines is  ++ (show lines))
is not accepted by either GHC or Hugs! Is this a bug or have stumbled into a 
context where it actually matters if you use '$' or explicit grouping with 
parentheses?

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

___
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,
actually: unsafeInterleaveIO.)

The program looks like 

Re: [Haskell] Implicit parameters redux

2004-01-28 Thread David Sankel
Ben,

  Could you explain in an extremely dumbed-down way what this is?  It would
be great if there were examples of

  1)  Some common, simple, and useful code in Haskell.
  2)  Same code using Implicit Parameters with a discussion of how it is
better.

Thanks,

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