Re: Mutable arrays in Haskell 98

2002-03-27 Thread José Romildo Malaquias

On Wed, Mar 27, 2002 at 03:58:46PM +, Malcolm Wallace wrote:
> José Romildo Malaquias <[EMAIL PROTECTED]> writes:
> 
> > I would like to use muttable arrays in Haskell 98, with the GHC
> > _and_ NHC98 compilers. By muttable arrays I mean arrays with
> > in-place updates, as with the MArray arrays (which are not
> > Haskell 98 conformant) found in GHC. Is such array implmentation
> > available?
> 
> Both compilers have libraries supporting the `IOArray' type,
> implemented with in-place update, although obviously the operations
> must be threaded through the IO monad.
> 
> module IOExtras   -- called IOExts in ghc
>   ( ... 
>   , IOArray -- data IOArray ix elt -- mutable arrays
>   , newIOArray  -- :: Ix ix => (ix,ix) -> elt -> IO (IOArray ix elt)
>   , boundsIOArray   -- :: Ix ix => IOArray ix elt -> (ix, ix)
>   , readIOArray -- :: Ix ix => IOArray ix elt -> ix -> IO elt
>   , writeIOArray-- :: Ix ix => IOArray ix elt -> ix -> elt -> IO ()
>   , freezeIOArray   -- :: Ix ix => IOArray ix elt -> IO (Array ix elt)
> 
>   , module Ix   -- re-export Ix for the benefit of IOArrays
> -- instance Eq (IOArray ix elt)
>   )

I am having difficults in defining a map function over an IOArray object.

My attempt was

  mapIOArray :: Ix ix => (a -> b) -> IOArray ix a -> IO (IOArray ix b)
  mapIOArray f v = do w <- newIOArray bounds 
  mapping w (range bounds)
  where
  bounds = boundsIOArray v
  mapping w (i:is) = do x <- readIOArray v i
writeIOArray w i (f x)
mapping w is
  mapping w [] = return w

But I do not know what to use to replace the . Is there
a polymorphic value in Haskell that can be of any type?

Is it indeed possible to have such function without resorting to
another intermediate data structure (like a list)?

Regards,

Romildo
-- 
Prof. José Romildo Malaquias   Departamento de Computação
http://iceb.ufop.br/~romildo   Universidade Federal de Ouro Preto
[EMAIL PROTECTED]   Brasil
[EMAIL PROTECTED]
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Mutable arrays in Haskell 98

2002-03-27 Thread José Romildo Malaquias

Hello.

I would like to use muttable arrays in Haskell 98, with the GHC
_and_ NHC98 compilers. By muttable arrays I mean arrays with
in-place updates, as with the MArray arrays (which are not
Haskell 98 conformant) found in GHC. Is such array implmentation
available?

Regards.

Romildo
-- 
Prof. José Romildo Malaquias   Departamento de Computação
http://iceb.ufop.br/~romildo   Universidade Federal de Ouro Preto
[EMAIL PROTECTED]   Brasil
[EMAIL PROTECTED]
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



[Newbie] Programming with MArray

2002-02-08 Thread José Romildo Malaquias

Hello.

To learn how to program with muttable arrays in Haskell, I have done
a very simple program to sum two arrays. I am submitting it to this
group so that it can be reviewd and commented. I have not find
examples on how to program with muttable arrays.

I would like for instance to see comments on the way the
iteration over the array indices was done: using a list
of indices. I looked for a way of incrementting an
index, starting from the lower bound towards the upper
bound, but failed in finding it. Is there other ways of
iterating over the muttable array other then using
its list of indices?

Regards,

Romildo
-- 
Prof. José Romildo Malaquias   Departamento de Computação
http://iceb.ufop.br/~romildo   Universidade Federal de Ouro Preto
[EMAIL PROTECTED]   Brasil
[EMAIL PROTECTED]


module Main where

import MArray
import ST

addArray :: (Ix ix, Num a) =>
STArray s ix a -> STArray s ix a -> STArray s ix a -> ST s ()

addArray v1 v2 v3
| b1 == b2 && b1 == b3 = mapM_ update (indices v1)
| otherwise= error "Bounds mismatch in addArray"
where
b1 = bounds v1
b2 = bounds v2
b3 = bounds v3
update i = do x1 <- readArray v1 i
  x2 <- readArray v2 i
  writeArray v3 i (x1 + x2)

testAddArray = do v1 <- newListArray (1,10) [0..10]
  v2 <- newListArray (1,10) [1..10]
  v3 <- newArray_ (1,10)
  addArray v1 v2 v3
  getElems v3

main = do xs <- stToIO testAddArray
  print xs



Re: Position of arguments in function definition and performance

2002-02-07 Thread José Romildo Malaquias

The programs:

-- common part
module Main where

reverse1 [] ys = ys
reverse1 (x:xs) ys = reverse1 xs (x:ys)

reverse2 ys [] = ys
reverse2 ys (x:xs) = reverse2 (x:ys) xs

-- program t1
main = print (length $! reverse1 [1..200] [])

-- program t2
main = print (length $! reverse2 [] [1..200])

give the following execution times in my 256MB, AMD Athlon XP 1600
based (RedHat Linux 7.2) system running ghc 5.02.2:

EXECUTION TIMES
COMPILERCOMPILER OPTIONSt1  t2
ghc 1.503   1.516
ghc -O2 1.858   1.834
ghc -fvia-c 1.507   1.491
ghc -O2 -fvia-c 1.855   1.835
nhc98   3.734   1.559

Comments:
- The compiler option -O2 with ghc leads to slight worse execution time
- Execution times for t1 and t2 are similar with ghc.
- t2 executes aproximately 2.4 times faster than t1 when compiled with nhc98
- t2 executation time when compiled with nh98 is as good as when compiled
  with ghc

Conclusions:
- with ghc there is no significant difference in performance when switching
  the position of the arguments subject to pattern matching in the function
  definition
- with nhc98, it is better to pattern match on the last argument
- surprisingly, the ghc -O2 compiler option generated code is worst than
  no optimization
  
Romildo
-- 
Prof. José Romildo Malaquias   Departamento de Computação
http://iceb.ufop.br/~romildo   Universidade Federal de Ouro Preto
[EMAIL PROTECTED]   Brasil
[EMAIL PROTECTED]
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



Position of arguments in function definition and performance

2002-02-06 Thread José Romildo Malaquias

Hello.

Please, tell me which set of definitions below should I expected
to be more efficient: the reverse1 or the reverse2 functions.

reverse1 [] ys = ys
reverse1 (x:xs) ys = reverse2 (x:ys) xs

reverse2 ys [] = ys
reverse2 ys (x:xs) = reverse2 (x:ys) xs

The difference rely on the position of the argument in which the
pattern matching is done in the function definition.

Regards.

Romildo
-- 
Prof. José Romildo Malaquias   Departamento de Computação
http://iceb.ufop.br/~romildo   Universidade Federal de Ouro Preto
[EMAIL PROTECTED]   Brasil
[EMAIL PROTECTED]
___
Haskell mailing list
[EMAIL PROTECTED]
http://www.haskell.org/mailman/listinfo/haskell



ANNOUNCE: hmake-3.00 RPM packages

2002-01-21 Thread José Romildo Malaquias

I have built RPM packages for hmake-3.00, which are availabe
at

http://uber.com.br/romildo/

The packages were built in a RedHat Linux 7.2 system.

It would be nice if these packages could be copied to
the hmake site.

Romildo

On Mon, Jan 21, 2002 at 11:57:04AM +, Malcolm Wallace wrote:
>   hmake-3.00
>   --
> We are pleased to announce the release of version 3.00 of 'hmake',
> the Haskell program compilation manager.
> 
> http://www.cs.york.ac.uk/fp/hmake/
> 
> Features of hmake:
> * compiler independent
> * aware of .hi files in re-compilation analysis
> * respects cpp directives
> * supplies an optional Hugs-like interactive environment (hi)
> 
> New features in 3.00:
> * improved detection and configuration of compilers
> * multiple compilers of the same type are now permitted simultaneously
>   (e.g. ghc 4.08 + 5.02)
> * you can refer to compilers by simple name or absolute paths
> * a new separate tool 'hmake-config' manages hmakerc files
> * various Haskell preprocessors are now recognised and invoked
>   (e.g. happy, hsc2hs, c2hs, greencard) if the corresponding file
>   extension is found (.ly/.y, .hsc, .chs, .gc)
> * hooks for the forthcoming compiler-independent Haskell tracing
>   system ('portable' Hat) are included
> 
> Bug reports:
> Please send bug reports for 'hmake' to the mailing list
> [EMAIL PROTECTED]
-- 
Prof. José Romildo Malaquias   Departamento de Computação
http://iceb.ufop.br/~romildo   Universidade Federal de Ouro Preto
[EMAIL PROTECTED]   Brasil
[EMAIL PROTECTED]

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



Re: suggestion

2001-10-23 Thread José Romildo Malaquias

On Tue, Oct 23, 2001 at 09:37:15AM +0100, Simon Marlow wrote:
> > What do you all think about activating the mechanism that 
> > automatically includes the name of the list before the subject
> > of a mailing list email?
> > For example:
> > "[hugs-users] Installation problems" or "[haskell] newbie 
> > question".
> 
> I don't like the extra prefixes, but if most folk would prefer them then
> I can turn them on.  Let me know if you have a preference one way or the
> other (don't mail to the list).

I also do not like the extra prefixes. It is easy to organize the messages
from different lists in separate mailboxes (at least in my Linux machine)
so that there is no need to identify the list one message belongs by
its message. Besides that, the subjects would get  more difficult to
be quicly read looking when scanning the mailbox to choose what to
read.

Romildo
-- 
Prof. José Romildo Malaquias
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil
http://iceb.ufop.br/~romildo
[EMAIL PROTECTED] [EMAIL PROTECTED]

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



ANNOUNCE: nhc98-1.02 RPMS for RedHat Linux 7.0

2001-02-16 Thread José Romildo Malaquias

Hello.

I have built RPM packages for hmake-1.02 and nhc98-1.02
for RedHat Linux 7.0, available from

ftp://urano.iceb.ufop.br/pub/nhc98/

Romildo.
===

On Wed, Feb 14, 2001 at 01:27:48PM +, [EMAIL PROTECTED] wrote:
> We are pleased to announce the new release 1.02 of nhc98, a compiler
> for Haskell'98, written in Haskell'98.
> 
> http://www.cs.york.ac.uk/fp/nhc98/
> 
> It is available as a source package (which can be built via ghc, hbc,
> an existing nhc98 installation, or simply with a C compiler if you
> don't already have a Haskell compiler installed).
> 
> Binary packages are also currently available for ix86-Linux and
> sparc-solaris2.  Binary packages for other architectures can be
> added to the list if users contribute them.
> 
> 
> What's new
> --
> This is an interim release, mainly fixing bugs in nhc98-1.00.
> The tracing and debugging tool, Hat, is about to undergo some
> significant changes, so release 1.02 is a stable snapshot before we
> start to break too many things!
> 
> Amongst the many bugfixes, notable ones are as follows:
> 
> * Fixed a space-leak in the compiler.  Compilation now
>   requires approximately half the previous maximum heap,
>   and as a result, compile times are 5-10% faster.
> 
> * The raw speed of input and output for compiled programs is
>   now much faster, although you will probably only notice a
>   difference if your program is severely I/O-bound.
> 
> * Local infix declarations now work correctly.
> 
> * `newtype T a = T a' now works correctly.
> 
> * @-pattern-bindings are fixed.  This means that Happy-generated
>   parsers now compile correctly.
> 
> * We now accept {-# pragmas #-} in any source position, and
>   understand LINE pragmas.
> 
> Recent bugfixes and new features in Hat include:
> 
> * When a traced program is interrupted or terminates with an error,
>   you get a virtual stack trace of the computation "for free",
>   without having to start up a browser.
> 
> * Foreign imports (via the new common primitive FFI) with an
>   I/O result type are now also traced (previously only pure
>   foreign functions were traced).
> 
> * Interface and object files for tracing now have distinct
>   file suffixes: .T.hi and .T.o.  This improves matters enormously
>   when switching between normal and tracing versions of a program.
>   It also fixes some dependency bugs when building the tracing
>   version of the compiler.  Both the compiler and hmake have
>   knowledge of the new suffixes.
> 
> * Tracing versions of the following libraries have been added:
>  IO, Array, FFI, IOExtras.
>   (Still missing: Directory, System, Time, Locale, CPUTime, Random.)
> 
> 
> Regards,
> Malcolm
> 
> 
> --------
> To unsubscribe, send a message containing the word `unsubscribe' to:
>   [EMAIL PROTECTED]
> 

-- 
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil

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



ANNOUNCE: hmake-2.02 RPM packages

2001-02-08 Thread José Romildo Malaquias

On Thu, Feb 08, 2001 at 02:47:41PM +, Malcolm Wallace wrote:
> We are pleased to announce the release of version 2.02 of 'hmake',
> the intelligent compilation manager for Haskell compilers.
> 
> http://www.cs.york.ac.uk/fp/hmake/
> ftp://ftp.cs.york.ac.uk/pub/haskell/hmake/

I have built RPM packages for hmake-2.02, to be found
at

ftp://urano.iceb.ufop.br/pub/nhc98/

I have used ghc-4.08.2 in a RedHat Linux 7.0 box.

> What's new in 2.02?
> ---
> This is mainly a bugfix release.
> 
> * Improved error-reporting. When a module cannot be found, it
>   now shows where the demand for the module arose, and which
>   directories were searched. 
> * Added knowledge of extended file suffixes like .p.o, .T.o, and .T.hi. 
> * Fixed a bug in the generation of Makefile dependencies in the
>   presence of a -I option. 
> * Ghc's options "-syslib n" and "-package n" no longer need to be
>   enclosed in double quotes to protect them from hmake. 
> 
> Regards,
> Malcolm
> 
> ___
> Haskell mailing list
> [EMAIL PROTECTED]
> http://www.haskell.org/mailman/listinfo/haskell

Romildo
-- 
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil

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



Re: no non-typevariable in instance declarations

2000-11-15 Thread José Romildo Malaquias

On Wed, Nov 15, 2000 at 10:21:28AM +, Malcolm Wallace wrote:
> > (By the way, is there any plans to implement multiparameter type
> > classes and instance overlapping in NHC98?)
> 
> No-one at York has any current plans to implement MPTC or instance
> overlapping in nhc98.  However, other people would be most welcome
> to do so if they wished.

I should be finishing my current project this year and next year
I should start looking at functional language implementation.
I will be starting a graduate course  which may culminate in the
implementation of a new functional language with a better
system for overloading. As an exercise I may try implementing
some extensions to NHC98.

Regards,

Romildo
-- 
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil

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



Re: no non-typevariable in instance declarations

2000-11-14 Thread José Romildo Malaquias

On Tue, Nov 14, 2000 at 02:18:47PM -0800, Jeffrey R. Lewis wrote:
> José Romildo Malaquias wrote:
> 
> > On Tue, Nov 14, 2000 at 05:02:30PM +, Malcolm Wallace wrote:
> > > > class C a where
> > > > ty :: a -> String
> > > > instance (Num a) => C a where
> > > > ty _ = "NUM"
> > > > instance C Integer where
> > > > ty _ = "Integer"
> > >
> > > > Why GHC and NHC98 are more restrictive than Hugs?
> > >
> > > The instances for (Num a=> a) and Integer overlap, and are therefore
> > > forbidden by Haskell'98.
> >
> > But this is not relevant to my question. Removing the instance
> > declaration
> >
> >   instance C Integer where
> >   ty _ = "Integer"
> >
> > from the program (so that there is no instance overlapping now)
> > does not help. Both GHC and NHC98 still complains with the
> > same diagnostics as before. They are not accepting the
> > instance declaration
> >
> >   instance (Num a) => C a where
> >   ty _ = "NUM"
> >
> > because there is no non-type-variable component in the
> > instantiated type "a" above.
> >
> > Again, why they have this restrictions while Hugs has not?
> 
> GHC doesn't have this restriction either, but since it's not Haskell 98,
> you don't get it without some effort ;-).  The following combination of
> flags will convince GHC to like your program:
> 
> -fallow-overlapping-instances -fallow-undecidable-instances

Thanks, Jeff. I did not know about the -fallow-undecidable-instances
option to GHC. As I am already using some extensions from GHC
(existentialy quantified type variables, multiparameter type
classes, implicit parameters, overlapping instances) I think
I could use undecidable instances too. I hope new versions of
the Haskell language will include them.

Romildo
-- 
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil

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



Re: no non-typevariable in instance declarations

2000-11-14 Thread José Romildo Malaquias

On Tue, Nov 14, 2000 at 07:41:21PM +, Marcin 'Qrczak' Kowalczyk wrote:
> Tue, 14 Nov 2000 16:17:48 -0200, José Romildo Malaquias <[EMAIL PROTECTED]> 
>pisze:
> 
> > But this is not relevant to my question. Removing the instance
> > declaration
> > 
> >   instance C Integer where
> >   ty _ = "Integer"
> > 
> > from the program (so that there is no instance overlapping now)
> > does not help.
> 
> In this case your instance would be the only one possible (any other
> would overlap) and it could be equally well written as a plain function.

Any instance for a no-Num type will not overlap:

  instance (Num a) => C a where
ty _ = "NUM"

  instance C Char where
ty _ = "CHAR"

and the overloaded function cannot be written as
a plain function.

> Actually Haskell 98 has more severe restriction than non-overlapping
> instances. The instance head must be a type constructor applied to
> as many distinct type variables as needed to let the kinds match.
> "instance Foo [Int]" is as non-standard as "instance Foo a".

I am not understand the restriction well. I verified that
both Hugs and GHC, when using extensions, accepts
"instance C [Int]", but only Hugs accepts 
"instance (Num a) => C a".

Where is this issue presented in a simple way easily
understandable by regular Haskell programmers? Any pointers?

Romildo
-- 
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil

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



Re: no non-typevariable in instance declarations

2000-11-14 Thread José Romildo Malaquias

On Tue, Nov 14, 2000 at 05:02:30PM +, Malcolm Wallace wrote:
> > class C a where
> > ty :: a -> String
> > instance (Num a) => C a where
> > ty _ = "NUM"
> > instance C Integer where
> > ty _ = "Integer"
> 
> > Why GHC and NHC98 are more restrictive than Hugs?
> 
> The instances for (Num a=> a) and Integer overlap, and are therefore
> forbidden by Haskell'98.

But this is not relevant to my question. Removing the instance
declaration

  instance C Integer where
  ty _ = "Integer"

from the program (so that there is no instance overlapping now)
does not help. Both GHC and NHC98 still complains with the
same diagnostics as before. They are not accepting the
instance declaration

  instance (Num a) => C a where
  ty _ = "NUM"

because there is no non-type-variable component in the
instantiated type "a" above.

Again, why they have this restrictions while Hugs has not?

> Hugs allows overlapping instances.

When given the option +o

> So does GHC with a special flag (-foverlapping-instances I think).

Yes

> nhc98 does not provide type-system extensions to Haskell'98.

Not exactly. NHC98 provides at least the following
extension to Haskell 98:
* existentialy quantified type variables

(By the way, is there any plans to implement multiparameter type
classes and instance overlapping in NHC98?)

Thanks,

Romildo
-- 
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil

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



no non-typevariable in instance declarations

2000-11-14 Thread José Romildo Malaquias

Hello.

I found that Hugs differs from GHC 4.08.1 and from NHC98 1.00
in instance declarations where the instance head has only
type variables: Hugs accepts them while the other two rejects.

Attached is a small program that demonstrates it.

Hugs happily runs the program and outputs the list

   ["NUM","Integer","NUM"]

NHC98 spits the message

   In file ./t.hs:
   6:23 Found a but expected one of [ ( 

GHC is more verbose in its message:

   t.hs:6:
 Illegal instance declaration for `C a'
(There must be at least one non-type-variable in the instance head)

   Compilation had errors

Why GHC and NHC98 are more restrictive than Hugs?

This style of instantiation would be very helpful when
dealing with type extensions in Haskell (based on classes
to provide the interface for common operations on
the extendable type).

Regards,

Romildo
-- 
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil


module Main where

class C a where
ty :: a -> String

instance (Num a) => C a where
ty _ = "NUM"

instance C Integer where
ty _ = "Integer"

main = print [ty (234::Int), ty (234::Integer), ty (234::Double)]



Error compiling gtk+hs in Red Hat Linux 7.0

2000-11-04 Thread José Romildo Malaquias

Hello.

When trying to build gtk+hs from CVS I am
getting the following error message:


+ make
Entering preparation phase...
make[1]: Entering directory `/home/romildo/rpms/BUILD/gtk+hs-0.10.1/glib'
/usr/bin/c2hs --cppopts="-I/usr/lib/glib/include -I/usr/X11R6/include" glib.h GL
ist.chs
c2hs: Generic fatal error.

/usr/lib/gcc-lib/i386-redhat-linux/2.96/include/stdarg.h:43: (column 26) [FATAL]
 
  >>> Syntax error!
  The symbol `__gnuc_va_list' does not fit here.

make[1]: *** [GList.hs] Error 1
make[1]: Leaving directory `/home/romildo/rpms/BUILD/gtk+hs-0.10.1/glib'
make: *** [prep] Error 2


I am using c2hs from CVS. The system is Red Hat Linux 7.0.
Any clues?

Romildo
-- 
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil

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



Re: Passing an environment around

2000-10-27 Thread José Romildo Malaquias

On Fri, Oct 27, 2000 at 09:07:24AM -0700, Jeffrey R. Lewis wrote:
> José Romildo Malaquias wrote:
> 
> > On Thu, Oct 19, 2000 at 09:08:16AM -0700, Conal Elliott wrote:
> > > Indeed Fran behaviors are like your alternative #1 (function passing), and
> > > hence sharing loss is a concern.  Simon PJ is right that I have a paper
> > > discussing this issue and some others.  See "Functional Implementations of
> > > Continuous Modeled Animation" on my pubs page
> > > (http://research.microsoft.com/~conal/papers).
> > >
> > > About alternative #2 (implicit arguments), would it help?  Does it eliminate
> > > the non-memoized redundant function applications, or just hide them?  For
> > > Fran, Erik Meijer suggested implicit functions to me a couple of years ago.
> > > I hadn't thought of it, and it did indeed seem to be attractive at first as
> > > a way to eliminate the need for overloading in Fran.  However, the (Time ->
> > > a) representation of Fran behaviors is not really viable, so I wouldn't
> > > merely want to hide that representation behind implicit arguments.
> >
> > It seems that implicit parameters does not eliminate redundant function
> > applications, as Conal Elliott has commented. Reading the paper
> >
> >Implicit Parameters: Dynamic Scoping with Static Types
> >Jefrrey Lewis, Mark Shields, Erik Meijer, John Launchbury
> >http://www.cse.ogi.edu/~jlewis/
> >
> > (especially section 5.1) I got this impression. I would like to hear
> > from others as well, as I had some difficulties with the paper.
> 
> I am sorry you had difficulties!

The difficulties I had is basicaly due to my lack of solid knowledge on
type theory and semantic formalisms. Not that the paper was badly
written.

> Yes, as implemented using the dictionary
> translation, implicit parameterization can lead to loss of sharing, exactly in
> the same way that overloading (and HOF in general) can lead to loss of sharing.
> 
> However, I can imagine that a compiler might chose to implement implicit
> parameters more like dynamic variables in lisp.   Each implicit param essentially
> becomes a global variable, implemented as a stack of values - the top of the
> stack is the value currently in scope.  This would avoid the sharing problem
> nicely.
> 
> --Jeff

I suppose your implementation of implicit parameterization in GHC and Hugs
uses the dictionary translation, right? Would an alternative implementation
based on a stack of values be viable and even done? Does it have serious
drawbacks when compared with the dictionary translation technique?

Thanks.

Romildo
-- 
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil

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



Overloaded function and implicit parameter passing

2000-10-23 Thread José Romildo Malaquias

Hi.

While experimenting with the implicit parameter
extension to Haskell 98, implemented in GHC 4.08.1
and latest Hugs, I came accross a difference among
those implementations regarding overloading functions
with implicit parameters.

As a test consider the program

- cut here
module Main where

class C a where
f :: (?env :: Integer) => a -> Integer

instance C Integer where
f x = ?env + x

main = putStrLn (show (f (45::Integer) with ?env = 100))
- cut here

Hugs accepts this program and outputs 145, as expected.
But GHC 4.08.1 refuses to compile it, emitting the
message

$ ghc -fglasgow-exts Test1.hs -o test1

Test1.hs:7:
Unbound implicit parameter `env_rJX :: Integer'
arising from use of `env_rJX' at Test1.hs:7
In the first argument of `+', namely `env_rJX'
In the right-hand side of an equation for `f': env_rJX + x

Compilation had errors

Would anybody comment on what is going on with GHC?

I am willing to use implicit parameters in the
software I am developing, but I have the need
to overload functions with implicit parameters.
While Hugs is good for development, its performance
may rule it out when the final product is ready.
So I will need a good Haskell compiler to compile
my system.

Any comments?

Romildo
-- 
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil

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



Re: Passing an environment around

2000-10-21 Thread José Romildo Malaquias

The following discussion is been conducted in the Clean mailing list.
As the issue is pertinent also to Haskell, I have cross-posted this
letter to the Haskell mailing list too.

Romildo.

On Thu, Oct 19, 2000 at 09:08:16AM -0700, Conal Elliott wrote:
> Indeed Fran behaviors are like your alternative #1 (function passing), and
> hence sharing loss is a concern.  Simon PJ is right that I have a paper
> discussing this issue and some others.  See "Functional Implementations of
> Continuous Modeled Animation" on my pubs page
> (http://research.microsoft.com/~conal/papers). 
> 
> About alternative #2 (implicit arguments), would it help?  Does it eliminate
> the non-memoized redundant function applications, or just hide them?  For
> Fran, Erik Meijer suggested implicit functions to me a couple of years ago.
> I hadn't thought of it, and it did indeed seem to be attractive at first as
> a way to eliminate the need for overloading in Fran.  However, the (Time ->
> a) representation of Fran behaviors is not really viable, so I wouldn't
> merely want to hide that representation behind implicit arguments.

It seems that implicit parameters does not eliminate redundant function
applications, as Conal Elliott has commented. Reading the paper

   Implicit Parameters: Dynamic Scoping with Static Types
   Jefrrey Lewis, Mark Shields, Erik Meijer, John Launchbury
   http://www.cse.ogi.edu/~jlewis/

(especially section 5.1) I got this impression. I would like to hear
from others as well, as I had some difficulties with the paper.

> I don't see how alternative #3 would work.
> 
> Of the three approaches, I think #1 is probably the best way to go.
> Functional programming encourages us to program with higher-order functions,
> and doing so naturally leads to this loss-of-sharing problem.  Memoization
> is thus a useful tool.  Adding it to Clean would probably help others as
> well as you.
> 
> 
> I recommend that you find out how real computer algebra systems address this
> issue.  I've used these systems some and have the impression that there is a
> default set of simplification rules, plus some strategies for non-standard
> "simplifications" like factoring.  You could apply the default set in a
> bottom-up way, with no need for memoization.  This is precisely the approach
> used for algebraic simplification in Pan (an Haskell-based image synthesis
> library).  See the recent paper "Compiling Embedded Languages" on my pubs
> page.  You can also get the Pan source release to check out the real
> details.
> 
> Good luck, and please let me know how it turns out.
> 
>   - Conal
> 
>  -Original Message-
> From: Simon Peyton-Jones  
> Sent: Thursday, October 19, 2000 1:51 AM
> To:   José Romildo Malaquias; [EMAIL PROTECTED]
> Cc:   Conal Elliott (E-mail); Meurig Sage (E-mail)
> Subject:  RE: [clean-list] Passing an environment around
> 
> It's interesting that *exactly* this issue came up when Conal
> Eliott was implementing Fran in Haskell.  His 'behaviours'
> are very like your expressions. 
>   type Behaviour a = Time -> a
> and he found exactly the loss of sharing that you did.
> 
> For some reason, though, I'd never thought of applying the
> implicit-parameter
> approach to Fran.  (Perhaps because Implicit parameters came along after
> Fran.)  
> But I think it's rather a good idea. 
> 
> I think Conal may have a paper describing the implementation choices
> he explored; I'm copying him.
> 
> Simon
> 
> | -Original Message-
> | From: José Romildo Malaquias [mailto:[EMAIL PROTECTED]]
> | Sent: 18 October 2000 08:12
> | To: [EMAIL PROTECTED]
> | Subject: [clean-list] Passing an environment around
> | 
> | 
> | Hello.
> | 
> | I am implementing a Computer Algebra system (CALG) in Clean, 
> | and I have a
> | problem I would like the opinion of Clean programmers.
> | 
> | The CALG system should be able to simplify (or better, to transform)
> | algebraic expressions (from Mathematics) involving integers, 
> | named constants
> | (like "pi" and "e"), variables, arithmetic operations (addition,
> | multiplication, exponentiation), and other forms of expressions
> | (trigonometric, logarithmic, derivatives, integrals, 
> | equations, etc.). The
> | tansformaations should follow the rules from Algebra and 
> | other areas of
> | Mathematica. But we know that in general an algebraic 
> | expression can be
> | transformed in different ways, depending on the goal of the
> | transformation. Thus, the algebraic expression
> | 
> |a^2 + b^2 + 3*a*b - a*b
> | 
> | could result in
> | 
> |a^2 + 2*a*b + b^2
> | 
&

Re: Extensible data types?

2000-10-20 Thread José Romildo Malaquias

Hello.

I am back with the issue of extensible union types. Basically
I want to extend a data type with new value constructors.
Some members of the list pointed me to the paper

   "Monad Transformers and Modular Interpreters"
   Sheng Liang, Paul Hudak and Mark Jones

The authors suggest using a type constructor to express
the disjoint union of two other types:

   data Either a b = Left a | Right b

which indeed is part of the Haskell 98 Prelude. Then they introduce
a subtype relationship using multiparameter type classes:

   class SubType sub sup where
  inj :: sub -> sup -- injection
  prj :: sup -> Maybe sub   -- projection

The Either data type consructor is then used to express
the desired subtype relationshipe:

   instance SubType a (Either a b) where
  inj   = Left
  prj (Left x)  = Just x
  prj _ = Nothing

   instance SubType a b => SubType a (Either c b) where
  inj   = Right . inj
  prj (Right x) = prj x
  prj _ = Nothing

The authors implemented their system in Gofer, due to
restrictions in the type class system of Haskell.
But now that there are Haskell extensions to support
multiparametric type classes, that could be implemented
in Haskell.

The above code fails to type check due to instances
overlapping. Hugs gives the following error message:

   ERROR "SubType.hs" (line 10): Overlapping instances for class "SubType"
   *** This instance   : SubType a (Either b c)
   *** Overlaps with   : SubType a (Either a b)
   *** Common instance : SubType a (Either a b)

(I did not check Gofer, but is there a way to solve these
overlapping of instances in it?)

So this is scheme is not going to work with Haskell (extended
with multiparameter type classes).

I would like hear any comments from the Haskell comunity on
this subject. Is there a workaround for the overlapping instances?

Regards.

Romildo
-- 
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil

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



NHC98 and GHC 4.08.1 differ on monad related functions

2000-10-14 Thread José Romildo Malaquias

Hello.

While porting Haskore to NHC98 I got an error
I am not understanding. I have attached a test
module that shows the error message:

$ nhc98 -c Test.hs


Error after type deriving/checking:
No default for  Monad.MonadPlus at 7:1.(171,[(2,209)])
No default for  Monad.MonadPlus at 6:1.(174,[(2,208)])

GHC 4.08.1 and Hugs98 accepts the code without
complaining.

Any hints?

Romildo
-- 
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil


module Test where

import Monad

zeroOrMore, oneOrMore :: MonadPlus m => m a -> m [a]
zeroOrMore m  = return [] `mplus` oneOrMore m
oneOrMore  m  = do { a <- m; as <- zeroOrMore m; return (a:as) }




Binary files and NHC98

2000-10-13 Thread José Romildo Malaquias

Hello.

In order to experiment with the Binary module
distributed with nhc98, I wrote the attached
program which writes a binary file and then
reads it. When executed, I got an extra
byte (8) that I cannot explain:

[65,66,67,68,8]

Any clues why it appears?

Regards,

Romildo
-- 
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil


module Main where

import IO (IOMode(ReadMode,WriteMode))
import Binary (openBin,closeBin,getBits,putBits,isEOFBin,
   BinIOMode(RO,WO),BinLocation(File),BinHandle)

-- convert from IOMode to BinIOMode
ioModeToBinIOMode   :: IOMode -> BinIOMode
ioModeToBinIOMode ReadMode   = RO
ioModeToBinIOMode WriteMode  = WO

-- open a binary file
openBinaryFile  :: FilePath -> IOMode -> IO BinHandle
openBinaryFile path mode = openBin (File path (ioModeToBinIOMode mode))

-- write a list of integers (8 bits) to binary file
writeBinaryFile :: FilePath -> [Int] -> IO ()
writeBinaryFile fileName xs =
do f <- openBinaryFile fileName WriteMode
   let writeToBin [] = return ()
   writeToBin (x:xs) = do putBits f 8 x
  writeToBin xs
   writeToBin xs
   closeBin f

-- read a list of integers (8 bits) from binary file
readBinaryFile  :: FilePath -> IO [Int]
readBinaryFile fileName =
do f <- openBinaryFile fileName ReadMode
   let readFromBin = do eof <- isEOFBin f
if eof
   then return []
   else do x <- getBits f 8
   xs <- readFromBin
   return (x:xs)
   xs <- readFromBin
   closeBin f
   return xs

-- test the above
main = do writeBinaryFile "test.bin" [65,66,67,68]
  xs <- readBinaryFile "test.bin"
  putStrLn (show xs)



Haskore and nhc98

2000-10-13 Thread José Romildo Malaquias

Hello.

I am just curious whether anybody has already
tried Haskore (http://www.haskell.org/haskore/)
with the NHC98 Haskell compiler. I am trying to
do it, while GHC 4.08.1 is non functional in my
RH Linux 7.0 box.

Romildo
-- 
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil

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



Re: haskell-mode and XEmacs

2000-04-30 Thread José Romildo Malaquias

On Sun, Apr 30, 2000 at 06:38:16AM +0100, Glynn Clements wrote:
> 
> José_Romildo_Malaquias wrote:
> 
> > I have been using the haskell-mode <http://www.haskel.org/haskell-mode/>
> > (latest release: 1.3) for (X)Emacs for a while and it has helped me a lot
> > in my Haskell programming activity. Thanks to the authors. But I am having
> > a problem with this mode in XEmacs (XEmacs 21.1.9). For every buffer I open
> > in haskell mode I receive the message
> > 
> > (error/warning) Error in `post-command-hook' (setting hook to nil): (void-variable 
>imenu--index-alist)
> 
> Try putting
> 
>   (require 'imenu)
> 
> in your ~/.emacs.

That solved the problem.

On Sat, Apr 29, 2000 at 10:26:05PM -0700, tom wrote:
> Have you tried running completely without your .emacs file?
> As a quick fix, have you tried setting imenu-index-alist to NIL?

I tried running without the system and user init files and then
progressively loaded the haskell-mode components. The error happens
with the module haskell-doc.el. Maybe it could be modified to
remove the need of explicitly requiring imenu.

Now my initialization file contais the following lines:

-
(setq load-path (cons "/usr/share/emacs/site-lisp/haskell-mode/" load-path))

(setq auto-mode-alist
  (append auto-mode-alist
  '(("\.[hg]s$"  . haskell-mode)
("\.hi$" . haskell-mode)
("\.l[hg]s$" . literate-haskell-mode

(autoload 'haskell-mode "haskell-mode"
   "Major mode for editing Haskell scripts." t)

(autoload 'literate-haskell-mode "haskell-mode"
   "Major mode for editing literate Haskell scripts." t)

(add-hook 'haskell-mode-hook 'turn-on-haskell-font-lock)
(add-hook 'haskell-mode-hook 'turn-on-haskell-decl-scan)

(require 'imenu)

(add-hook 'haskell-mode-hook 'turn-on-haskell-doc-mode)
(add-hook 'haskell-mode-hook 'turn-on-haskell-indent)

;(add-hook 'haskell-mode-hook 'turn-on-haskell-simple-indent)
(add-hook 'haskell-mode-hook 'turn-on-haskell-hugs)
-

Thanks for pointing me for a solution.

Romildo
-- 
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil




haskell-mode and XEmacs

2000-04-29 Thread José Romildo Malaquias

Hello.

I have been using the haskell-mode <http://www.haskel.org/haskell-mode/>
(latest release: 1.3) for (X)Emacs for a while and it has helped me a lot
in my Haskell programming activity. Thanks to the authors. But I am having
a problem with this mode in XEmacs (XEmacs 21.1.9). For every buffer I open
in haskell mode I receive the message

(error/warning) Error in `post-command-hook' (setting hook to nil): (void-variable 
imenu--index-alist)

in a new window. This is becoming annoying as I open my Haskell files. As I do
not know the details of Emacs Lisp programming, could someone please take a
look at the mode and try to correct it. Note that this message does not appear
in GNU Emacs.

Regards,

Romildo
-- 
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil




[TEST] Please, ignore.

2000-04-14 Thread José Romildo Malaquias

Is the list down? The latest message I received was on Apr 11.
-- 
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil




Announce: nhc98-1.0pre17 rpms

2000-03-19 Thread José Romildo Malaquias

I have packaged nhc98 in RPM format in a RedHat
Linux 6.1 box. The files can be found on

ftp://urano.iceb.ufop.br/pub/nhc98/

Note: It has not been extensively tested. I have
just compiled a "hello world" program to see 
whether it works. (it did.)

To the author: I noticed that configuring the 
installation dir using configure hard codes the
dir into the nhc98 script. Is it the only file
afected or the dir is made into some other files
(like binary files)? I am asking because in the
process of building the rpm the install phase uses
a temporary dir to make the install into. Only
when binary rpm package is installed, the files
go to the final location for them.

Romildo
-- 
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil



Re: Dynamic scopes in Haskell

1999-12-03 Thread José Romildo Malaquias

Is there any references to memoization techniques? I could not find
any reference to memoization facilities in the Haskell report and
library report. Neither in the Clean report. After looking at GHC,
Hugs98 and nhc98, I have found that GCH provides the memo function
used in the example. Looking at it, it does not look easily portable.

So, is it straightforward to implement the memo function in
Haskell 98 or in Clean?

Romildo
==
On Thu, Dec 02, 1999 at 12:08:58PM +0100, Koen Claessen wrote:
> Michael Erik Florentin Nielsen <[EMAIL PROTECTED]> writes:
> 
>  | There are no problems in having infix operators with more than two
>  | parameters, eg. the operators `plus` and `times` below both take a third
>  | parameter: [...]
> 
> The problem is that you lose sharing. If you define:
> 
>   newtype N a
> = N (Env -> a)
> 
>   plus :: N Int -> N Int -> N Int
>   plus (N f) (N g) = N (\env -> f env + g env)
> 
> (Your numbers would just be N Int, with Env = Int). And then later,
> you say:
> 
>   let x :: N Int
>   x = veryBigExpression
>  
>in plus x x
> 
> Then "veryBigExpression" depending on an "Env" gets computed twice if you
> finally provide the "Env".
> 
> One solution is to define "N" to be a monad, in order to be explicit about
> sharing.
> 
>   do x <- veryBigExpression
>  ... x ... x ... -- no problem here
> 
> This clutters up the expressions a lot, so it is no acceptable
> solution.
> 
> Another solution, which works in this case, is to memoize the function in
> an N. So instead of using the constructor N directly, you use "memoN":
> 
>   memoN :: (Env -> a) -> N a
>   memoN f = N (memo f)
> 
> If you redefine all operations as follows:
> 
>   plus :: N Int -> N Int -> N Int
>   plus (N f) (N g) = memoN (\env -> f env + g env)
> 
> Then the problem is gone.
> 
> I used this trick recently to create a Haskell binding to a theorem prover
> that required an extra argument (the theorem prover object) to every
> "binary" operator. It works well in practise.
> 
> One possible problem though is that you lose equality on types like "N a".
> If you really want equality *and* sharing, (but care a little bit less
> about some particular laws that Haskell "has" -- which are by the way not
> defined anywhere anyway) you might want to take a look at the following
> paper:
> 
>   "Observable Sharing for Functional Circuit Description", 
>   Koen Claessen, David Sands, ASIAN '99.
>   Available from: http://www.cs.chalmers.se/~koen/publications.html
> 
> Regards,
> Koen.
> 
> --
> Koen Claessen http://www.cs.chalmers.se/~koen 
> phone:+46-31-772 5424  e-mail:[EMAIL PROTECTED]
> -
> Chalmers University of Technology, Gothenburg, Sweden
> 

-- 
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil



Re: Dynamic scopes in Haskell

1999-12-02 Thread José Romildo Malaquias

On Thu, Dec 02, 1999 at 11:11:12AM +0100, Michael Erik Florentin Nielsen wrote:
> 
> > My problem:
> > --
> > One of the algorithms I have to implement is the
> > addition of symbolic expressions. It should have
> > two symbolic expressions as arguments and should
> > produce a symbolic expression as the result. But
> > how the result is produced is depending on series
> > of flags that control how the expressions is to
> > be manipulated. This set of flags should then be
> > passed as a third argument to addition function.
> > This is the correct way of doing it. But, being
> > a Mathematics application, my system should preserve
> > the tradicional Math notation (that is, infix
> > operators with suitable associations defined). So
> > my symbolic expression type should be an instance
> > of the Num class so that the (+) operator can
> > be overloaded for it. But, as the function has
> > now three arguments, it cannot be a binary operator
> > anymore.
> 
> There are no problems in having infix operators with more than two
> parameters, eg. the operators `plus` and `times` below both take a third
> parameter:
> 
>   infixl 6 `plus`
>   infixl 7 `times`
> 
>   int :: Int->(Int->Int)
>   int n x = n
> 
>   x :: (Int->Int)
>   x y = y
> 
>   plus :: (Int->Int)->(Int->Int)->(Int->Int)
>   (a `plus` b) x = a x + b x
> 
>   times :: (Int->Int)->(Int->Int)->(Int->Int)
>   (a `times` b) x = a x * b x
> 
> This allows for expressions such as (x `times` (int 1 `plus` x)) 7 that
> evaluates to 56.  Replacing + and * for `plus` and `times`, that is
> making (a suitable newtype over) Int->Int into an instance of Num is
> more or less trivial - except for some silly choices when making the Eq
> instance:  Whether expressions of this type are equal should probably
> depend on the environment.  But as the return type of == is Bool the
> environment will not be available and you would have to make == a dummy
> function.

This solution seems to fit my problem. I will just investigate it
a little more. Thanks.

> In fact you would probably be better of by hiding the prelude
> and overloading + and friends on your own.

Is there any directions on how to hide the prelude and still use the
definitions it exports?

Romildo.
-- 
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil



Re: Dynamic scopes in Haskell

1999-12-01 Thread José Romildo Malaquias

On Wed, Dec 01, 1999 at 01:33:01PM +0100, Ch. A. Herrmann wrote:
> Hello,
> 
> > operators with suitable associations defined). So
> > my symbolic expression type should be an instance
> > of the Num class so that the (+) operator can
> > be overloaded for it. But, as the function has
> > now three arguments, it cannot be a binary operator
> > anymore.
> 
> maybe, an ad-hoc solution is to use an interpreter
> which takes your infix expressions as strings and evaluates them in
> the environment you like.

This is not a solution for my problem, because what am developing
is a library in Haskell for symbolic manipulation. So the user of
the library will be programming in Haskell. An interpreter at this
level would be inadequate.

I have developed a solution in the current version of my library
(in Clean) in which I have had a different approach: the environment
was attached to the expressions been evaluated. But it seems to
have some problems... I have also developed an interpreter (in Clean)
that reads symbolic expressions, parses them, simplify them and
prints the result. The parser converts from strings to the representation
used in the library for the symbolic expressions. But this
interpreter is just an application of the library, not its goal.

> 
> For the future, I would appreciate a redesign of the overloading
> of operators in Haskell, such that any (also predefined) operator
> can be overloaded according to the users taste,
> e.g., to form an expression like
> 
> expr1 +e expr2
> 
> where e is some environment and the above expression is shorthand for 
> 
> (+) e expr1 expr2.
> 
> -- 
>  Christoph Herrmann
>  E-mail:  [EMAIL PROTECTED]
>  WWW:     http://brahms.fmi.uni-passau.de/cl/staff/herrmann.html
> 
> 
> 
> 

-- 
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil



Re: Dynamic scopes in Haskell

1999-12-01 Thread José Romildo Malaquias

On Wed, Dec 01, 1999 at 08:59:09AM -0800, Jeffrey R. Lewis wrote:
> "Ch. A. Herrmann" wrote:
> 
> > I had just a fast look at the following I found at the
> > page "http://www.cse.ogi.edu/PacSoft/projects/Hugs/hugsman/exts.html"
> > for dynamic scoping:
> >
> >min :: [a] -> a
> >min  = least with ?cmp = (<=)
> >
> > Actually, I'm not sure how referential transparency can be established
> > with these implicit parameters. Assume min to be called at two places
> > with a different value for cmp, but with the same input list. Or is it
> > the case that the type a is bound to a particular cmp all over the program?
> >
> > Please note, that referential transparency is one main advantage Haskell
> > has in contrast to other languages .
> 
> A paper on implicit parameters will appear in POPL'00 that will answer this
> sort of question.  I'll post a reference to it later when I get a chance to
> put it on my web page.

The paper can already be found on Mark Shields home page, as I have just
discovered. The URL is

http://www.cse.ogi.edu/~mbs/pub/implicit.ps.gz

> 
> But in short, for `min' to be called in two places, within the same lexical
> scope, with different bindings for `?cmp' implies that there's an intervening
> `with' binding in that same lexical scope.  To avoid the problem you allude
> to, we extended substitution, particularly thru `with' bindings, to preserve
> dynaming scoping (i.e. to prevent dynamic capture).  Thus referential
> transparency is retained, you just have to be careful when you substitute -
> just as you have to be careful with regular static name capture.
> 
> --Jeff
> 

-- 
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil



Re: Dynamic scopes in Haskell

1999-12-01 Thread José Romildo Malaquias

On Wed, Dec 01, 1999 at 02:05:04PM +, Jerzy Karczmarczuk wrote:
> José Romildo Malaquias:
> 
> > One of the algorithms I have to implement is the
> > addition of symbolic expressions. It should have
> > two symbolic expressions as arguments and should
> > produce a symbolic expression as the result. But
> > how the result is produced is depending on series
> > of flags that control how the expressions is to
> > be manipulated. This set of flags should then be
> > passed as a third argument to addition function.
> > This is the correct way of doing it. But, being
> > a Mathematics application, my system should preserve
> > the tradicional Math notation (that is, infix
> > operators with suitable associations defined). So
> > my symbolic expression type should be an instance
> > of the Num class so that the (+) operator can
> > be overloaded for it. But, as the function has
> > now three arguments, it cannot be a binary operator
> > anymore.
> 
> ... then about Monads e algumas outras coisinhas mais
> ou menos bonitas.
> 
> ==
> 
> I don't fully understand the issue. If it is only 
> a syntactic problem, and for a given chunk, say,
> a module, your set of flags is fixed, and does not change
> between one expression and another, you can always define

No, it is not only a syntatic problem and the set of flags is
not fixed. Indeed it may change in the course of some
computation. Some algorithms will set some flags based on
the values of other flags during the computation. It may be
the case that the same function is recursively applied
with a different set of flags.

A simple example of the style of programming am talking
about can be seen in the following example (in Hugs98,
loaded with the extensions):
---
module Context where

data Context = Context { num_num :: Int, branch :: Bool }

som :: (?c :: Context) => Rational -> Rational -> Rational
som x y
  | num_num ?c > 0 = x + y
  | otherwise  = x - y

mul :: (?c :: Context) => Rational -> Rational -> Rational
mul x y
  | num_num ?c > 0 = x * y
  | otherwise  = x / y

f :: (?c :: Context) => Rational -> Rational
f x = let a = som x 2
  n = num_num ?c
  b = mul x 5 with ?c = Context { num_num = - n, branch = True }
  in mul a b

run = dlet ?c = Context { num_num = 3, branch = False }
  in f 8

main = putStr (show run)
---

Note that som, mul and f uses the context and f also evaluates a
subexpression in a new context. main evaluates (f 8) in an initial
context.

> 
> add flagSet x y = ...-- your addition function--
> 
> and then overload
> 
> x+y = add myCurrentEnv x y
> 
> in this module.

So, your sugestion will not work for me.

> (I can't resist complaining once more about
> the inadequacy of the Num class hierarchy in Haskell ...;
> one will have to do the same in the Rational or Floating
> instance definitions, which is clumsy).
> 
> Jerzy Karczmarczuk
> Caen, France

Romildo
-- 
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil



Dynamic scopes in Haskell

1999-12-01 Thread José Romildo Malaquias

The scope:
-
Looking at the Hugs98 (November release) I found an
interesting extension: dynamic scoped variables.
(for reference, just read the Hugs98 documentation,
that can be found at their site).

<http://www.cse.ogi.edu/PacSoft/projects/Hugs/hugsman/exts.html>

This extension just come to what I have been
looking for to use in a Computer Algebra system
am developing. It has been too hard to accomplish
what I want without them.

My problem:
--
One of the algorithms I have to implement is the
addition of symbolic expressions. It should have
two symbolic expressions as arguments and should
produce a symbolic expression as the result. But
how the result is produced is depending on series
of flags that control how the expressions is to
be manipulated. This set of flags should then be
passed as a third argument to addition function.
This is the correct way of doing it. But, being
a Mathematics application, my system should preserve
the tradicional Math notation (that is, infix
operators with suitable associations defined). So
my symbolic expression type should be an instance
of the Num class so that the (+) operator can
be overloaded for it. But, as the function has
now three arguments, it cannot be a binary operator
anymore.

Monads are not suitable:
---
I thought about hiding the environment (the set of
flags mentioned above) inside a reader monad, but
then there will a series of problems about the
notation and the Math notation will be impossible.

Dynamic scoping is the solution:
---
If I could pass around the environment indirectly to
my addition function, then it would remain a 2-argument
function and would be implemented as
binary operator. Defining the environment as dynamic scoped
variable just do it for me. In fact, that is how the
computer algebra system has been implemented in its first
version using the Scheme programming language.

The questions:
-
I can develop my system in Hugs98 using this extension. But
I will end up with a program that is non-portable across
other Haskell implementations. So,

- Is dynamic scoping a stablished feature in Hugs98?
  (Will it continue to be offered in next releases, or is
  it just experimental and may be dropped soon?)

- Is it feasible to incorporate this feature into the
  next version of Haskell?

- Does other Haskell implementations (ghc, nhc, hbc, ...)
  would provide this extension in next releases? (This way,
  even been an extension, my system would be portable) 

Any comments on these subject will be apreciated.

Regards.

J. R. Malaquias
-- 
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil



How to use an state reader monad?

1999-11-30 Thread José Romildo Malaquias

I came across an implementation of reader monads by Andy Gill,
<http://www.cse.ogi.edu/~andy/monads/MonadReader.htm>
inspired by the paper "Functional Programming with Overloading
and Higher-Order Polymorphism" (by Mark P Jones)
<http://www.cse.ogi.edu/~mpj/pubs/springschool.html>:

-- 
-- Reader monads.
-- A class of monads for describing computations that
-- consult some fixed environment.

class (Monad m) => ReaderMonad s m where
-- asks for the (internal non-mutable) state
ask :: m s

-- this allows you to provide a projection function
asks :: (ReaderMonad s m)  => (s -> a) -> m a
asks f = do s <- ask
return (f s)

-- a parametarized reader monad
newtype Reader w a = Reader { runReader :: w -> a }

instance Functor (Reader w) where
fmap f m = Reader ( \w -> f (runReader m w) )

instance Monad (Reader w) where
return v = Reader ( \w -> v )

p >>= f  = Reader ( \w -> runReader (f (runReader p w)) w )

fail str = Reader ( \w -> error str )

instance ReaderMonad w (Reader w) where
ask = Reader ( \w -> w )
-- -

Would someone write a simple Haskell program that ilustrates how
one can use this reader monad?

I have tried the following, but it fails at compilation:

---
test = do env <- ask
  if env == "choose a"
  then return 'a'
  else return 'b'

do_test = runReader test "choose a"

main = putStr (show do_test)
---

Thanks.

Romildo
--
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil



Re: CICS, Haskell, and CAS

1999-11-29 Thread José Romildo Malaquias

Dear Ben,

I have implemented a symbolic algebra system about ten years ago
in Scheme. It was named SICS (Sistema Interativo de Computação
Simbólica -- Interactive Symbolic Computer System). It was developed
in PC Scheme. Nowadays PC Scheme is not available anymore -- and
I lost my PC Scheme diskettes. The code I wrote is not "standard
Scheme" and it does not run in other Scheme implementations out of
the box. If I had the time I would port it to a more "stard Scheme"
so it could run on most Scheme implementations.

Recently I have worked out a computer algebra system (which I have
named CAlg), based on this previous work.
My primarily implementation is done in the Clean programming
language, but I am in the process of porting it to Haskell. It has not been
released to the public, since it still needs some polishing.

I have documented the basics of CAlg (although the documentation is
still somewhat evolving) and am going to present it as my master
thesis early next year in ITA (Instituto Tecnológico de Aeronáutica,
Brazil).

Dr. Eduardo Costa has informaly helped me with this project.

I intend to soon release a public version of CAlg.

Romildo.

On Sun, Nov 28, 1999 at 04:13:48PM -0500, Ben wrote:
> A recent thread on the Haskell mailing list spawned a discussion on
> computer algebra systems. It was mentioned that you have already
> written one in Scheme called CICS and that you have written a document
> (monograph) describing the process of implementing one.
> 
> Is CICS still available some where? Would you send me a copy of your
> monograph?
> 
> Thanks,
> Ben.

-- 
Prof. José Romildo Malaquias <[EMAIL PROTECTED]>
Departamento de Computação
Universidade Federal de Ouro Preto
Brasil