Re: Fundeps and quantified constructors

2001-02-08 Thread anatoli


--- Tom Pledger <[EMAIL PROTECTED]> wrote:
> anatoli writes:
>  :
>  | The same error message is given for
>  | 
>  | > data Foo a = (Eq b) => MkFoo b
> 
> Since the type variable a is orphaned, how about reducing it to this?
> 
> > data Foo = forall b . Eq b => MkFoo b

This is possible (the semantics is different of course).
What I want to do is, given a multi-parameter context,
orphan one type variable leaving the other intact,
and that's not possible now. I can only orphan all or preserve 
all.

> 
> so that  MkFoo :: Eq b => b -> Foo
> 
>  | I don't know whether this is intended behaviour; IMHO
>  | it should be treated identically to
>  | 
>  | > data Foo a = MkFoo (Eq a => a)
> 
> Isn't the Foo-ed a hidden by the Eq-ed a in this example too?  i.e.
> 
> > data Foo = MkFoo (forall a . Eq a => a)

It appears that both examples are wrong, or at least Hugs thinks so.
The first MkFoo happily accepts any type, not just of class Eq:

Main> :t MkFoo head
MkFoo head :: Foo ([a] -> a)

The second accepts nothing of interest:
Main> :t MkFoo 'a' 
ERROR: Inferred type is not general enough
*** Expression: 'a'
*** Expected type : Eq a => a
*** Inferred type : Eq Char => Char

Hm... The more I experiment with this, the less I understand.

It seems that the only correct place to put the quantifier
is before the data constructor, and the context may go either
before the type constructor or after the quantifier. This is 
very unfortunate. How can I correctly write something to this
effect:

> data Quick a = Eq  a => Unsorted [a]
>  | Ord a => Sorted (Tree a)

???

Regards
-- 
anatoli

__
Do You Yahoo!?
Get personalized email addresses from Yahoo! Mail - only $35 
a year!  http://personal.mail.yahoo.com/

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



Re: Revamping the numeric classes

2001-02-08 Thread Bjorn Lisper

>> >Also, what is the inferred type of, for example
>> >f x y = x + length y
>> >? It can be
>> >Int -> [a] -> Int
>> >[Int] -> [a] -> [Int]
>> >and neither is more general than the other. And this is a simple
>> >function.
>> 
>> Int -> [a] -> Int, since this is the type it will get in the original type
>> system.

>So I can't apply f to lists, but I could if I inline its body. This
>means that I cannot arbitrarily refactor a piece of code by moving
>parts of it into separate definitions: subexpressions are given
>some extra meanings only if they are physically placed in certain
>contexts. This is bad.

This is a misunderstanding. the transformation of f l y , where l :: [Int]
for instance, should depend only on the type of f and not its definition.
It is the call to f, not f itself, that becomes transformed. No inlining
takes place.

>Ah, so what uses of f are correct depends on its definition, not type!
>Sorry, this is way to radical.

>Types exist to formalize possible ways a value can be used. HM allows
>to determine most general types variables in a let-block (or: of a
>module) before their uses, so separate compilation is possible. In
>your system typechecking of a function's definition is done each time
>it is used!

No. See above.

Björn Lisper

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



Re: Revamping the numeric classes

2001-02-08 Thread Bjorn Lisper

>> It is quite similar in spirit to the concept of principal type in
>> Hindley-Milner type systems. An expression can have many types but
>> only one "best" (most general) type in that system.

>Now, I'm not any kind of expert on this, but isn't the most general
>HM type one that encompasses the others, and *not* one out of a set of
>ambigous (and mutually exclusive) types?

In a sense. You define a partial order on types by a < a' (a more general
than a') if there is a substitution s of type variables such that
a' = sa. The interesting property of HM type systems is that for each term t
and all type judgements t:a that can be derived, there is a type judgement
t:a' such that a' < a. a' is called the most general type of t.

What I suggested was to define a different relation between types, measuring
"relative liftedness". We can call it "<<". Now, if it is the case that for
all judgements t -> t':a in the type system I sketch, there is a judgement
t -> t'':a' where a' << a, the we can select the transformation to be
t -> t''. t'' will then have a "most general type" among the possible
transformed terms, but wrt << rather than <.

Ambiguity between types depends on the ordering between types that you
consider!

Björn Lisper

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



Re: please help me

2001-02-08 Thread Ch. A. Herrmann

Hi Faizan,

> "FAIZAN" == FAIZAN RAZA <[EMAIL PROTECTED]> writes:

FAIZAN> Hello Please help me to solve this questions


FAIZAN> Question

FAIZAN> Cartesian Product of three sets, written as X x Y x Z is
FAIZAN> defined as the set of all ordered triples such that the
FAIZAN> first element is a member of X, the second is member of Y,
FAIZAN> and the thrid member of set Z. write a Haskell function
FAIZAN> cartesianProduct which when given three lists (to represent
FAIZAN> three sets) of integers returns a list of lists of ordered
FAIZAN> triples.

FAIZAN> For examples, cartesianProduct [1,3][2,4][5,6] returns
FAIZAN> [[1,2,5],[1,2,6],[1,4,5],[1,4,6],[3,2,5],[3,2,6],[3,4,5],[3,4,6]]

I'll leave that as an exercise for you :-)

If you want to become a Haskell programmer, try it yourself.

Two hints: - have a look at list comprehensions in the report
   - first try to solve it with two sets and pairs

Cheers
Christoph

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



Re: binary files in haskell

2001-02-08 Thread John Meacham

Since there seems to be general support for the idea of some sort of
Portable Byte IO package, I will work on am implementation of my
proposal for ghc being the platform I am most familiar with. I really
like the simplicity of the hPut and hGet idea and will probably use it
as my mechanism for implementation on ghc, however for a Portable API
which should be implementable across a wide variety of Haskell 98
implementations and machine architectures it is too low level to allow
certain portable applications to be written. I made the API at pretty
much the exact level of the Haskell 98 IO API since it seems to strike a
good balance between portability and expressiveness/power. 

A nice advantage of using my mid-level routines is that there are very
little requirements placed on 'Byte' as a type, this means that as long
as to the outside world you only read in 8 bit values and spit 8 bit
values out you can represent it internally however you want. 

for example you might have a machine where a 16 bit word is the smallest
addressable entity, if you relied on hPut Word8 then your program would
not work since Word8 cannot exist on that platform. however if you made
Byte be 16 bits and only used the bottom half of each word then your
program will run unchanged even among architectures such as this.

my requirements for Byte were going to basically mirror the C
requirements for char, The smallest individually addressable integral
type greater than 8 bits in width. The trick that makes programs using
Byte portable is that ByteIO.read and ByteIO.write only utilize the
lower 8 bits of that datatype at a time, therefore one can write
portable Haskell applications which work on network sockets and file
streams in a machine independent fashion.

Anyone who is concerned about the space requirements of using up a
little more memory than necessary on certain architectures will have to
know about how those architectures store stuff in memory anyway to pack
values into the architecture primitives properly so they can use hPut
and hGet with explicit word widths...


I guess what would be nice would be a portable ByteIO as the standard
mid-level interface and the hPut, hGet idea available on those platforms
which support Storable since they seem to make sense as the primitives
for Haskell implementations which allow such fine grained access to the
hardware representations.  (but such access should not be required from
a haskell implementation in order to write portable programs which can
communicate in externally defined formats)

John


-- 
--
John Meacham   http://www.ugcs.caltech.edu/~john/
California Institute of Technology, Alum.  [EMAIL PROTECTED]
--

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



Re: Revamping the numeric classes

2001-02-08 Thread Marcin 'Qrczak' Kowalczyk

On Thu, 8 Feb 2001, Bjorn Lisper wrote:

> >> Int -> [a] -> Int, since this is the type it will get in the original type
> >> system.

> This is a misunderstanding. the transformation of f l y , where l :: [Int]
> for instance, should depend only on the type of f and not its definition.
> It is the call to f, not f itself, that becomes transformed. No inlining
> takes place.

I see. So you can transform arbitrary function of type a->b->c
to a function of type [a]->b->[c], by applying
\f x y -> map (\z -> f z y) x
and similarly a->b->c to a->[b]->[c]. But then there are two ways of
transforming a->b->c to [a]->[b]->[[c]] and the order of applying the
former transformations does matter. Worse: a third way is to apply zipWith
and then promote the result to a single-element list. Or maybe map the
result to a list of single-element lists... Sorry, IMHO it's ambiguous as
hell except very simple cases.

-- 
Marcin 'Qrczak' Kowalczyk


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



Re: binary files in haskell

2001-02-08 Thread Fergus Henderson

On 08-Feb-2001, John Meacham <[EMAIL PROTECTED]> wrote:
> A nice advantage of using my mid-level routines is that there are very
> little requirements placed on 'Byte' as a type, this means that as long
> as to the outside world you only read in 8 bit values and spit 8 bit
> values out you can represent it internally however you want. 
> 
> for example you might have a machine where a 16 bit word is the smallest
> addressable entity, if you relied on hPut Word8 then your program would
> not work since Word8 cannot exist on that platform. however if you made
> Byte be 16 bits and only used the bottom half of each word then your
> program will run unchanged even among architectures such as this.

I agree that `Byte' is a useful abstraction.
However, I think what you say about Word8 here is not correct.
Word8 can be implemented on a 16-bit machine just by computing all
arithmetic operations modulo 256.  There is no requirement that Word8
be physically 8 bits, just that it represents an 8-bit quantity.

Indeed, I think ghc uses this technique, representing Word8 as a full
machine word (e.g. 32 bits for x86, of which the topmost 24 are always
zero).

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
|  of excellence is a lethal habit"
WWW:   | -- the last words of T. S. Garp.

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



Re: names, modules, types

2001-02-08 Thread Johannes Waldmann

> There is exponential growth of possibilities in compound expressions.
> And I'm afraid that ambiguities would happen in unexpected places and
> it would not be easy to find where to add type signatures. Especially
> as there is less explicit type information than in many other
> statically typed languages.

Yes, I see that. However I think that adding type signatures
is good programming practice anyway, and I wouldn't mind if a future Haskell 
required me to do some explicit typing (for top-level definitions, say).

What are the ergonomic benefits of allowing the programmer
to omit type declarations? It does invite sloppy programming, no?
And does it make life easier or harder for the compiler (writer)?

Best regards,
-- 
-- Johannes Waldmann  http://www.informatik.uni-leipzig.de/~joe/ --
-- [EMAIL PROTECTED] -- phone/fax (+49) 341 9732 204/252 --

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



Re: names, modules, types

2001-02-08 Thread Fergus Henderson

On 07-Feb-2001, Marcin 'Qrczak' Kowalczyk <[EMAIL PROTECTED]> wrote:
> So why is fmap separate now? Probably because having too much
> overloading causes ambiguities.

Perhaps.  But I think there may be other reasons too.

Having fmap separate is useful for beginners and for teaching,
because you can describe `map' without having to talk about type classes.
Also, it is possible that the error messages that you get when you
make a mistake using `fmap' might be harder to understand.

The reasoning here is similar to the reasons that Haskell 98 has list
comprehensions rather than monad comprehensions.

-- 
Fergus Henderson <[EMAIL PROTECTED]>  |  "I have always known that the pursuit
|  of excellence is a lethal habit"
WWW:   | -- the last words of T. S. Garp.

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



Re: Revamping the numeric classes

2001-02-08 Thread Bjorn Lisper

>I see. So you can transform arbitrary function of type a->b->c
>to a function of type [a]->b->[c], by applying
>\f x y -> map (\z -> f z y) x
>and similarly a->b->c to a->[b]->[c]. But then there are two ways of
>transforming a->b->c to [a]->[b]->[[c]] and the order of applying the
>former transformations does matter. Worse: a third way is to apply zipWith
>and then promote the result to a single-element list. Or maybe map the
>result to a list of single-element lists...

There should be no transformation to type [a]->[b]->[[c]] in this case.
If f is applied to arguments of type [a] and [b] then this should be
interpreted as the elementwise application of f to the two argument lists,
and the result type should then be [c]. Note that [a]->[b]->[[c]] is
"more lifted" than [a]->[b]->[c].

Elementwise application to one argument should transform to map, of several
arguments to zipWith with appropriate arity.

It is easier to see how it should work if we skip lists, so we don't have to
deal with maps and zipWiths and other list functions.  Let us consider
elementwise application of f over indexed entitites. For simplicity we
consider functions as our indexed entities, but it could as well be arrays.
With f as above, then f x y should be transformed to:

(1) x :: d -> a, y :: b yields \i -> f (x i) y
(2) x :: a, y :: d -> b yields \i -> f x (y i)
(3) x :: d -> a, y :: d -> b yields \i -> f (x i) (y i)

Here (3) is "full" elementwise application, and (1) and (2) are "partial"
elementwise applications where the unlifted argument can be seen as
promoted.  If you have list instead of functions, then the transformation
should insert list primitives with the corresponding effect.

>Sorry, IMHO it's ambiguous as hell except very simple cases.

Of course the type/term transformation system must have the property that
if different transformations can yield the "best" type (wrt liftedness),
then the transformed expressions should be semantically equivalent. I believe
a type/term transformation system with this property can be designed, but
the details remain to be worked out.

Björn Lisper

(Is this discussion still of interest to the Haskell list members? Or should
we take it offline?)

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



Re: FranTK

2001-02-08 Thread Jan Kort

Hi Petra,

Since you are a system administrator, I asume that you will also
want to install FranTk so other people can use it. I'm not sure
this is possible. I did manage to get it working for myself localy,
but a "make install" doesn't do anything.

If you are in a hurry, you can use the fixes below and let the users
copy your directory and make their programs in the FranTk/demos
directory. The whole directory is about 27M.

Like always, a better solution is to wait a little:
According to the news on the FranTk homepage the library will become
part of hslibs. This means that it will be distributed with ghc and
it should also have a proper installation. I would wait for that.

I will CC the mail to [EMAIL PROTECTED], maybe someone there can
give you an estimate on when FranTk will be released as part of
hslibs.

Regards,
  Jan

To get FranTk for ghc 4.06 to work with ghc 4.08 apply the following fixes:

Run configure like normal, i.e.:
./configure --prefix=/scratch/kort/pkgs/frantk

Change the file FranTk/src/FranSrc/Compatibility.ghc.hs to

-- this module is for GHC; GSL
module Compatibility
   ( double2Float
   , yield
   , debugMsgLn
   , setDebug
   , mkWeakIORef
   , toInt
   , fromInt
   ) where
import GlaExts 
import NumExts(doubleToFloat)
import PrelRead(readDec)
import IOExts
import Concurrent
import Exception

double2Float = doubleToFloat

setDebug :: Bool -> IO ()
setDebug _ = return ()

debugMsgLn :: String -> IO ()
debugMsgLn s = assert (trace s `seq` True) $ return () 


In the file FranTk/src/FranTkSrc/Makefile change the line:
HC_OPTS+= -i../FranSrc:../TclHaskellSrc -fallow-overlapping-instances 
-fallow-undecidable-instances
-syslib misc 
to:
HC_OPTS+= -i../FranSrc:../TclHaskellSrc -fallow-overlapping-instances 
-fallow-undecidable-instances
-syslib data

In the file FranTk/demos/Makefile change the line:
HC_OPTS+= -i../src/FranTkSrc:../src/FranSrc:../src/TclHaskellSrc 
-fallow-overlapping-instances
-fallow-undecidable-instances -syslib misc
to:
HC_OPTS+= -i../src/FranTkSrc:../src/FranSrc:../src/TclHaskellSrc 
-fallow-overlapping-instances
-fallow-undecidable-instances -syslib data

If the compiler complains about not finding the file "tcl.h", in the
file FranTk/src/TclHaskellSrc/Makefile change the rule:
tclhaskell.o: tclhaskell.c tclhaskell.h
$(HC) -c tclhaskell.c
to:
tclhaskell.o: tclhaskell.c tclhaskell.h
$(HC) -I/opt/arch/lib/tk8.3/include -c tclhaskell.c
where /opt/arch... is the place "tcl.h" and "tk.h" are.

In the directory FranTk/src/TclHaskellSrc do:
rm *.hi *.o

In the file FranTk/src/TclHaskellSrc/Makefile add TclPrim.hs to
the HS_SRCS list.

In the directory FranTk/src/FranSrc do:
rm *.hi

In the directory FranTk/demos do:
rm *.hi

And then continue the normal installation with:
gmake boot
gmake all

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



Re: FranTK

2001-02-08 Thread Johannes Waldmann


> want to install FranTk so other people can use it. I'm not sure
> this is possible.

sure it is .. and it is rather easy to make it known to ghc
(so that -syslib frantk works). just add these lines to the driver script
(around line 2740, where all the other syslib entries live)

   frantk,
[  # where to find the archive to use when linking
  ( $INSTALLING 
   ? "$InstLibDirGhc"
   : "$TopPwd/hslibs/frantk"
  )
, # no cbits archive
  ''
, 'lang data concurrent' # Syslib dependencies
, '' # extra ghc opts
, '' # extra cc opts
, '-ltk8.0 -ltcl8.0 -lX11 -lm -ldl' # extra ld opts
 # where to slurp interface files from
, ( $INSTALLING 
   ? ( "$InstLibDirGhc/imports/frantk" )
   : ( "$TopPwd/hslibs/frantk" )
  )
],

and move all the hi files to $TopPwd/imports/frantk, 
and libfrantk.a to $TopPwd/libHSfrantk.a

by the way, if you use `hmake', be sure to set GHCINCDIR and GHCINCPATH
so that it knows about ghc's interface files.

then, you can use  `hmake "-syslib frantk" Foo'  to make your project.
(i think you need the double quotes.)


best regards
-- 
-- Johannes Waldmann  http://www.informatik.uni-leipzig.de/~joe/ --
-- [EMAIL PROTECTED] -- phone/fax (+49) 341 9732 204/252 --

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



Re: `Covertible' class. Reply.

2001-02-08 Thread Marc van Dongen

S.D.Mechveliani ([EMAIL PROTECTED]) wrote:

[snip]

: The basic algebra library BAL 
:  http://www.botik.ru/pub/local/Mechveliani/basAlgPropos/bal-pre-0.01/
:  
: suggests class Cast a b where cast :: a -> b -> a

I just want to add that this is almost similar to a
mechanism I've implemented. You really need this.

Regards,


Marc van Dongen

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



ANNOUNCE: hmake-2.02

2001-02-08 Thread Malcolm Wallace

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/

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



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: "Job Adverts" on haskell.org

2001-02-08 Thread Benjamin L. Russell

On Tue, 06 Feb 2001 15:27:54 +
 "C.Reinke" <[EMAIL PROTECTED]> wrote:
> 
> > Haskell.org has a page "Job Adverts".
> > http://www.haskell.org/jobs.html
> 
> [snip]
> 
> A Adverts for positions involving Haskell
>   - Positions in Academia
>   - Positions in Industry
> 
> [snip]

Why not add a internships as a third subsection for section A, so it would look as 
follows:

A Adverts for positions involving Haskell
- Positions in Academia
- Positions in Industry
- Internships

Starting a full programming position is a major project, but an internship can be more 
accessible.  Currently, it is difficult for self-starters not currently enrolled in a 
university or working a Haskell-related job to tiptoe into Haskell-land.  An 
internship would offer this kind of opportunity, especially if it can be done either 
on weekends or over the Internet.

--Ben
--
Benjamin L. Russell
[EMAIL PROTECTED]
[EMAIL PROTECTED]
"Furuike ya!  Kawazu tobikomu mizu no oto."  --Matsuo Basho

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



Re: names, modules, types

2001-02-08 Thread Marcin 'Qrczak' Kowalczyk

Thu, 8 Feb 2001 12:46:29 +0100 (MET), Johannes Waldmann 
<[EMAIL PROTECTED]> pisze:

> Yes, I see that. However I think that adding type signatures is
> good programming practice anyway, and I wouldn't mind if a future
> Haskell required me to do some explicit typing (for top-level
> definitions, say).

Types of top-level definitions are not enough when every identifier
can have many completely unrelated types, and types of subexpressions
are derived both from their contents and context.

> What are the ergonomic benefits of allowing the programmer
> to omit type declarations? It does invite sloppy programming, no?
> And does it make life easier or harder for the compiler (writer)?

Adding overloading like in C++ certainly it makes life harder for the
compiler writer. IMHO it does not work at all in a language with HM
type system when the type inference does not proceed inside-out only.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


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



Re: Revamping the numeric classes

2001-02-08 Thread Marcin 'Qrczak' Kowalczyk

Thu, 8 Feb 2001 13:39:51 +0100 (MET), Bjorn Lisper <[EMAIL PROTECTED]> pisze:

> >I see. So you can transform arbitrary function of type a->b->c
> >to a function of type [a]->b->[c], by applying
> >\f x y -> map (\z -> f z y) x
> >and similarly a->b->c to a->[b]->[c]. But then there are two ways of
> >transforming a->b->c to [a]->[b]->[[c]

> There should be no transformation to type [a]->[b]->[[c]] in this case.

Wait wait wait. You told that a->b->c is convertible to [a]->b->[c]
for *any* a,b,c. Now I have x = [a], y = b, z = [c] and use the
transformation x->y->z to x->[y]->[z] and obtain [a]->[b]->[[c]].

Both steps are legal, so their composition must be legal, or I don't
like this Haskell-like language anymore.

Unless you say that a->b->c is convertible to a->[b]->[c] *except*
when a is a list. Then it's bad again. There should be no negative
conditions in the type system! Moreover, in a polymorphic function
you don't know yet if a will be a list or not.

> Here (3) is "full" elementwise application, and (1) and (2) are
> "partial" elementwise applications where the unlifted argument can
> be seen as promoted.

There are no full and partial applications because of currying.
It's impossible to say when you should consider a function as a
multiparameter function. There are only single-argument functions.
So you would have to say that some rule apply only *unless* the result
has a function type, which does not work again.

With your rules a programmer writes code which is meant to implicitly
convert a value to a single-element list, because something tries
to iterate over it like on a list. Unfortunately the element happens
to be a string, and he gets iteration over its characters. And if it
works the other way, another programmer meant iteration over characters
and got iteration over a single string. You can't tell which was meant.

Generally the concept of treating a single element as a list (promoting
it when necessary) is ambiguous in its nature and it should not be used
in any general purpose language. It might work in a poor language which
operates only on numbers, vectors and matrices, but not in Haskell in
which lists are perfectly first class objects, and similarly functions,
and whose type system is polymorphic, so operations can be applied to
values which are lists or not, functions or not, not statically known.

> Of course the type/term transformation system must have the property that
> if different transformations can yield the "best" type (wrt liftedness),
> then the transformed expressions should be semantically equivalent.

It's not enough, because the least lifted type is not the most general
answer. Answers for different amounts of liftedness are incompatible
with that answer - they are not its instances as in the HM typing.

There is no most general answer, so these rules are ambiguous and
cannot be designed well.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


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



Re: `Covertible' class. Reply.

2001-02-08 Thread Marcin 'Qrczak' Kowalczyk

Thu, 08 Feb 2001 09:41:55 +0300, S.D.Mechveliani <[EMAIL PROTECTED]> pisze:

> If  s  is an element of a certain domain, then one can use the
> construction  
>  cast s x
> 
> to convert various data  x  to corresponding canonical values in the
> domain defined by  s.

Defining a domain by a sample argument is neither elegant (most of
the time it's not needed because the type determines the domain)
nor general (when considering domains not defined by types, there
can be more than one domain sharing a value of the carrier type).
So this is generally a bad idea.

-- 
 __("<  Marcin Kowalczyk * [EMAIL PROTECTED] http://qrczak.ids.net.pl/
 \__/
  ^^  SYGNATURA ZASTÊPCZA
QRCZAK


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