Re: [Haskell] Initialisation without unsafePerformIO

2004-06-04 Thread Jorge Adriano Aires

 What ideas do people have for getting rid of unsafePerformIO?

Hope my suggestion is not too naive. 
I get along quite fine using implicit parameters in many cases, it's just 
tedious explicitly typing them in every function context. I'd be pretty happy 
if it was possible to define the 'scope' of some implicit parameters in a 
module and/or define their scope as being a whole module. The 2nd option 
would be something like:

 module (?par :: Parameter) = A where 
 ...

Functions in A could have ?par in their context without having it explicitly 
typed. Now the import of A could be done with:

 module B where 

 import A  -- simple, ?par unbound
 import A as Ak where ?par = k -- ?par bound to k
 import A as Am where ?par = m -- ?par bound to m

 ...

 k :: Parameter
 k = ...
 
 m :: Parameter
 m = ...
 ...

Also,

 module (?par :: Parameter) = C where 
 import A  -- both A and C paremeterised by ?par

Since both modules share the same parameter, instantiation on ?par in the 
import of C would propagate to the import of A.

At first glance it seems simple syntactic sugar and therefore doable. 
Along with some options in the interpreter to hide/show (this kind of) 
implicit parameters when displaying signatures, check module context, etc. 
probably also quite usable.

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


Re: [Haskell] Initialisation without unsafePerformIO

2004-06-03 Thread George Russell
Chung-chieh Shan wrote (snipped):
 The enabling technique behind our solution is to propagate values
 via types (literally), with the help of polymorphic recursion and
 higher-ranked polymorphism.  The technique essentially emulates
 local type-class instance declarations.  Configuration parameters
 are propagated throughout the code implicitly as part of type
 inference rather than explicitly by the programmer.
Crikey!  You represent configuration values which are
integers by encoding them as a type with constructors
   data Zero
   data Twice s
   data Succ s
   data Pred s
and you encode general values which are instances of Storable
by casting their binary representation (pinned by a StablePtr)
into bytes and then encoding the result as integers.  My mind
boggles.  It would be nice if your paper included an appendix
containing a main program which, say, used a graphics library
including configuration parameters in your style.  (Say,
default font (string), font size (integer) and mouse handedness
(bool).)
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] Initialisation without unsafePerformIO

2004-06-01 Thread George Russell
What ideas do people have for getting rid of unsafePerformIO?
The most common use of unsafePerformIO, for me at least, is initialisation.
There *surely* must be a better way of doing this, but I haven't really
seen much discussion of the topic.  Here is my back-of-the-envelope
suggestion for a new interface, can anyone do better?
type Dict 
-- a collection of initialised data.

register :: Typeable a = Dict - a - IO ()
-- register a value of type (a) in the dictionary.  Only one value of each
-- type is allowed in the dictionary; registering the same type twice will
-- cause an exception.
defaultDict :: IO Dict
-- Each Haskell main program will have one of these.
lookup :: Typeable a = Dict - IO a
-- Get the value of (a) registered in the Dict, or raise an exception if it
-- isn't.
Thus, libraries which rely on internal initialised state will also have
to provide a function which initialises that state.  I don't think this is
very painful.  IME it's often required anyway, if you want to provide the
library with additional parameters.  Also the library could catch the
exception from (lookup) and give a helpful error message of the form
You forgot to run Gadgets.initialise.
We can also provide additional dictionaries.
thisThreadDict :: IO Dict
newEmptyDict :: IO Dict
runWithDifferentDefaultDict :: Dict - IO a - IO a
This would allow the programmer much more control over initialisation.
For example, programs distributed over a large number of processors are
no longer obliged to use a single global dictionary, which is effectively
what is required now.  (How else can you make sure that two processors do
not try to evaluate the same unsafePerformIO value at once?)  And
runWithDifferentDefaultDict allows you to change the value returned by
defaultDict during an action, meaning that programs can for example
initialise the same library multiple times, which would be useful during
debugging.
Well it's a start I think.  Can anyone do better?
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Initialisation without unsafePerformIO

2004-06-01 Thread John Meacham
On Tue, Jun 01, 2004 at 06:06:36PM +0200, George Russell wrote:
 What ideas do people have for getting rid of unsafePerformIO?
 
 The most common use of unsafePerformIO, for me at least, is initialisation.
 There *surely* must be a better way of doing this, but I haven't really
 seen much discussion of the topic.  Here is my back-of-the-envelope
 suggestion for a new interface, can anyone do better?

I am a fan of allowing top level declarations of the form:

foo - newIORef foo

which would behave as an initializer, with the semantics being that it
be evaluated at most once before foos first use. (so it could be
implemented via unsafePerformIO or as an init section run before main).

The 
{-# NOINLINE foo #-}
foo = unsafePeformIO $ newIORef foo

idiom is so common and useful, it should have some compiler support. It
is 'clean' too, since all we are doing is extending the world with new
state, but in a much cleaner/safer way then writing to a file or environment
variable or other methods of storing state in the world.

John
-- 
John Meacham - repetae.netjohn 
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell