Segmentation faults with ghc-4.02 code

1999-02-19 Thread Meurig Sage

Hi folks,
I tried to compile the following program with both ghc-3.02 and ghc-4.02

(pathlevel 1), using the linux glibc binary releases. The 3.02 one works

fine but the code produced by 4.02 segmentation faults when I try to run

it.

It uses a c program, which links to code in tcl-tk v8.0. I've included
the tclhaskell.c and tclhaskell.h files at the end of this mail.

I compiled with
gcc -c -I/usr/local/opt/include  -I/usr/local/opt/include
-I/usr/X11/include  tclhaskell.c
ghc-4.02 -O -fvia-C -fglasgow-exts -c '-#include "tclhaskell.h"' Main.hs

ghc-4.02 -O -fvia-C -fglasgow-exts -ltk8.0 -ltcl8.0 -lX11 -lm -lc -ldl
-L/usr/local/opt/lib  -L/usr/local/opt/lib  -L/usr/X11/lib  -L/usr/lib
-L/lib -o main Main.o tclhaskell.o
and similarly for ghc-3.02

Thanks
  Meurig

--- Main.hs
-
module Main where

main :: IO ()
main = do
 primInitTcl
 primExecuteTcl_ "button .b -text ben"
 primExecuteTcl_ "pack .b"
 loop
  where
   loop = do
still - primRunTcl
if still then loop
 else return ()

primInitTcl :: IO Bool
primInitTcl = map' int2bool $ _ccall_ primInitTcl

primExecuteTcl_ :: String - IO ()
primExecuteTcl_ s = _ccall_ primExecuteTcl_ s

primRunTcl :: IO Bool
primRunTcl = map' int2bool (_ccall_ primRunTcl)

map' :: (a - b) - IO a - IO b
map' f io = do
  x - io
  return $ f x

int2bool :: Int - Bool
int2bool 0 = False
int2bool n = True


-- tclhaskell.h
--
void primPutEnv (char *str);
void primTclDebug(int flg);
int  primInitTcl(void);
int  primRunTcl(void);
char *primExecuteTcl(char *cmd);
void primExecuteTcl_ (char *cmd);
char *primGetEvent(void);
void primSetVar(char * varname,char * inp);

-- tclhaskell.c ---
/* 
 * tclhaskell.c --
 *
 *  Based on tkgofer.c from the TkGofer distribution.
 *  Changes by Chris Dornan ([EMAIL PROTECTED]).
 *
 * This file contains the interface for the "haskell-tcl" link.
 * It is based on tkMain.c - the main program of wish.
 *
 * It supports a new tcl-command
 * - haskell_event n: to write the string n into the event buffer
 *
 * The provided gofer primitives are
 * - primInitTcl   : to initialze tcl/tk, returns 1 if successful
 * - primRunTcl  : to start the eventloop of tcl/tk
 *  - primExecuteTcl : to evaluate an event by the tcl
interpreter
 * - primGetEvent   : to read the event buffer
 * buffer contains event identification
 * plus bind arguments
 *  - primSetVar : write user output into tcl variables
 *
 */

#include stdio.h
#include stdlib.h

#include tcl.h
#include tk.h

#include sys/types.h
#include sys/stat.h
#include unistd.h

#include "tclhaskell.h"


void  primPutEnv(char *str)
{
  char *cpy = malloc(strlen(str)+1);

  if (str!=NULL) {
strcpy(cpy,str);
putenv(cpy);
  }
}



/* 
* Declaration for debug information
 */

Bool tcl_debug=0;   /* TRUE  = show debug information */


/* 
 * Declaration for window and interpreter variables
 */

static Tcl_Interp *interp; /* Interpreter for this application.
*/

#define BUFFER_SIZE 2000   /* Buffers for communication
Contains identifier and
bind arguments
 */

#define QUEUE_SLOTS 20  /* The number of slots in the
buffer */

int queue_head, queue_tail, queue_full; /* The head, tail and full flag
of
the event queue, organised as a
cyclic buffer
 */

static char event_buffer[BUFFER_SIZE];   /* the event buffer */


/* 
 * Reporting Errors
 */

tkh_error(char *message)
{
  fprintf(stderr, "TclHaskell: %s\n", message);
}

tkh_abort(char *message)
{
  tkh_error(message);
  abort();
}


/* 
 * Buffer manipulation functions
 */

static int slot_size(void)
{
  return (BUFFER_SIZE/QUEUE_SLOTS);
}

static int slot_base(int i)
{
  return (i*slot_size());
}

static void inc_index(int *i)
{
  *i= (*i+1) % QUEUE_SLOTS;
}

static int init_queue(void)
{
  queue_head= queue_tail= queue_full= 0;
}

static int queue_empty(void)
{
  return (!queue_full  queue_head==queue_tail);
}

static void enqueue(char *str)
{
  if (str[0]==0) {
tkh_error("empty event string");
return;
  }
  if (strlen(str)+1slot_size()) {
tkh_error("event string too large");
return;
  }
  if 

Re: Q: Efficiency of Array Implementation

1999-02-19 Thread Jan Laitenberger


Dear Mr. Mechveliani,
 

 I thought efficient arrays are impossible in functional language.

I'm not sharing this thought...   

Here is a quote from the Haskell Library Report:

\begin{quote}
  ``Haskell provides indexable arrays, which may be thought of as functions
whose domains are isomorphic to contiguous subsets of the integers.
Functions restricted in this way can be implemented efficiently;
in particular, a programmer may reasonably expect rapid access to the
components.''
\end{quote}
   
 So we have to organise the data so that to avoid the access by index
  - as possible. 

Sure. If possible - ok.


Regards,

Jan

 ___
'---|--
|  __,   _  _  EMail: [EMAIL PROTECTED]
| /  |  / |/ | WWWeb: http://www.uni-passau.de/~laitenbe/
|/\_/|_/  |  |_/
   /| Laitenberger 
--(-|--
   \|



Re: Q: Efficiency of Array Implementation

1999-02-19 Thread S.D.Mechveliani

Concerning 'rapid access' you found in docs - it is hard to believe
this access is as fast as in C array - i mean changing X[i] in array
X. Because when this change is done fast, it is a side effect, breaks
functionality.
I always thought that this is the main cost the functional world pays
for the nice functional principles - to think of how to avoid indice
in the critical parts of the algorithm.
Well, i may mistake ...



Re: Q: Efficiency of Array Implementation

1999-02-19 Thread fis


 Date: Fri, 19 Feb 1999 09:41:58 +0100 (MET)
 From: Lennart Augustsson [EMAIL PROTECTED]
 CC: [EMAIL PROTECTED], [EMAIL PROTECTED],
 [EMAIL PROTECTED]


  Concerning 'rapid access' you found in docs - it is hard to believe
  this access is as fast as in C array - i mean changing X[i] in array
  X. Because when this change is done fast, it is a side effect, breaks
  functionality.
 Extracting values from an array can be as fast as in C.  The tricky
 part is contructing the array.  The Haskell Array module provides
 one way of constructing monolithic arrays, i.e., arrays that are built
 once and never again modified.
 But there are other ways, e.g., using ST monad which allows incremental
 construction of the array.

-- Lennart


This reminds me of a question I could not solve on my own yet (due to
lack of an operational profiler for the most part): Is it possible that
ghc knows how to transform Array data structures into destructive
arrays in some settings?

I had an algorithm with a terrible time complexity and wrote an
implementation using purely functional Arrays. Since the runtime was
still to bad, I tried ST together with MutableArrays instead, but the
runtime got worse.

I don't have the time to figure out the details right now, but if you
plan to stay interested in them for a longer period, tell me and I will
give you more information when I work on the problem again. (It's still
possible that it's a bug in my code, however.)


 -Matthias





-- 
Max-Planck-Institut für Informatik  |  DFKI
[EMAIL PROTECTED]   |  [EMAIL PROTECTED]
http://www.mpi-sb.mpg.de/~fis   |





Re: Haskell-2

1999-02-19 Thread Leon Smith

I'd like to see the numeric class hierarchy re-organized
along lines suggested by modern algebra.  That is,
it should be organized in terms of Groups, Rings,
Fields, etc., instead of Integral, Fractional, Real,
etc.   I have no idea how this should look exactly,
so I'll just request it and leave it to people smarter
than me to hammer out the details :-)

Yes, please.   I would greatly appreciate this.  Combining this with
exact/inexact type classes like Scheme would be wonderful.

I've played a little bit with setting up class systems along these lines.
However, I think that Haskell's type system is somewhat limited when it
comes to implementing such a hierarchy.  

Interestingly enough, I started to desire things that it sounds like
dependent types would answer.  (I.E. types from values, functions from
types to types, etc.)  I have not gotten a chance to look at Cayenne yet.
This discussion on dependent types has certainly piqued my curiosity.

With dependent types, would it be possible to get types from values (i.e.
types that you haven't actually declared before.)  One example would be the
group of integers modulo n.  It sounds to me like types would then be first
class.  So, concieveably, I could write a function Z : Integer - Type,
where Z n would be the group of integers modulo n.  


best,
leon







Lists and FP (was Re: Functions allowing either 0 or 1 parameters?)

1999-02-19 Thread Leon Smith

Don't be shy about using lists when writing Haskell Code.  Since Haskell is
lazy, lists are often consumed as they are created, so in many cases they
do not use extra memory.  Lists really are the key to clarity AND efficiency.

These definitions are the most efficient of those proposed for the problem:

More "elegant". That is, shorter:
 g :: Integer
 g = sum (map f [0..20])

A perhaps more efficient version of the previous function.
 g :: Integer
 g = foldl (\sum i - sum + (f i)) 0 [0..20]

In this particular case, pretty much any Haskell compiler will
automatically perform optimizations that will transform the first
definition into the second definition.  So, the first definition will
create the same object code as the second.  Even if the implementation
doesn't optimize it, the fact that Haskell is lazy means that there isn't a
huge difference between the two.  The following is how a implementation
would reduce our un-optimized expression:

   sum (map f [0..20])

 = foldl (+) 0 ( map f  (0 : [1..20]) )

 = foldl (+) 0 ( f 0 : (map f [1..20]) )

 = foldl (+) (0 + f 0) ( map f (1 : [2..20]) )

 = foldl (+) (0 + f 0) ( f 1 : (map f [2..20]) )

 = foldl (+) (0 + f 0 + f 1) ( map f [2..20] )

 ...

(Actually, to achieve the same efficiency, one would have to use fold'
instead of foldl in the second definition.  This is because foldl' uses
strictness annotations to improve its efficiency, and sum is actually
defined in terms of foldl'.  In our reduction sequence, this would amount
to evaluating the second argument of foldl immediately, instead of building
a expression that will be evaluated later.)

Now, doesn't the functional version express what you want to do more
concisely, clearly, and directly than its imperative counterpart?

   g = sum (map f [0..20])


   int g = 0;
   for (int i = 0, i = 20, i++) {
 g += f(i);
   }

The various list functions (foldl, foldr, scanl, scanr, etc.)  often take
the place of looping constructs in imperative languages.  In fact, FP is so
flexible that you can write functions that will "iterate" on values in
pretty much any way desired. 

I would strongly recommend reading "Introduction to Functional Programming
using Haskell, 2nd ed." by Richard Bird.  It is a really wonderful book.  

best,
leon

P.S.  One good demonstration of lists is computing factorials.  For
example, one could write:

   fact :: Integer - Integer
   fact 0   = 1
   fact (n + 1) = (n + 1) * fact n

Let's start Hugs and calculate 1!:

Main fact 1

(127701 reductions, 195550 cells, 2 garbage collections)
ERROR: Control stack overflow

This definition follows straightforwardly from the mathematical definition
of factorials.  However, it uses stack space proportional to n.  We could
achieve efficient tail recursion by this careful definition:  (Ignoring the
function's behavior on n  0)
 
   fact2 :: Integer - Integer 
   fact2  = impl 1

 where
impl :: Integer - Integer - Integer
impl x n | n = 1= x
 | otherwise = impl (x*n) (n-1)

Main fact2 1

(240449 reductions, 409653 cells, 18 garbage collections)
ERROR: Garbage collection fails to reclaim sufficient space

We have improved both the time and space efficiency of the definition.
However, we have run into memory problems because Haskell is lazy.
(Sometimes being lazy is good, other times it is bad!) Using strictness
annotations to solve this problem:

   fact3 :: Integer - Integer
   fact3 = impl 1
 where 
   impl :: Integer - Integer - Integer
   impl x n | n = 1= x
| otherwise = (impl $! (x*n)) (n-1)

Main fact3 1
284625968091705451890641321211986{Interrupted!}

(190012 reductions, 47622336 cells, 590 garbage collections) 

And 124 seconds of time on my somewhat elderly PC. 

Not expecting anything better, we could try a fourth definition using lists:

  fact4  :: Integer - Integer
  fact4 n = product [1..n]

Main fact4 1
2846259680917054518906413212119868890148{Interrupted!}

(210031 reductions, 42217590 cells, 520 garbage collections)

Surprisingly, this took only 110 seconds.  After all this work, we find
that the definition that makes careful use of lists is also the most
efficient, readable, and concise.  Looking at the definition of product and
fold:

   product = foldl' (*) 1

Where foldl' is just a strict version of foldl.

In FP, there are two incredibly useful functions that deal with lists:
foldl and foldr. (Pronounced fold-left and fold-right respectively.)

   foldl   :: (a - b - a) - a - [b] - a
   foldl f a [] = a
   foldl f a (x:xs) = foldl f (f a x) xs

   foldr   :: (b - a - a) - a - [b] - a
   foldr f z [] = z
   foldr f z (x:xs) = f x (foldr f z xs)


We can define a function that will find the sum of a list with these


 sum = foldr (+) 0
 -- OR
 sum = foldl {+} 0


One useful way to think about foldl and foldr is that
   sum (1 : 2 : 3 : 4 : 5 : [])
=  foldr (+) 0 (1 : (2 : (3 : (4 : (5 : [])

Re: Haskell 2 -- Dependent types?

1999-02-19 Thread Lennart Augustsson


 OK, I'm curious.  Two people replied that C++ has undecidable type
 checking.  I was not aware of this (although I can't say I'm too
 surprised); do you have a reference?
It's actually the template processing that can loop, but it is
sort of part of the type checking.

You can find an article in the POPL 99 proceeding about it.

-- Lennart





Re: Haskell 2 -- Dependent types?

1999-02-19 Thread Fergus Henderson

On 18-Feb-1999, Carl R. Witty [EMAIL PROTECTED] wrote:
 OK, I'm curious.  Two people replied that C++ has undecidable type
 checking.  I was not aware of this (although I can't say I'm too
 surprised); do you have a reference?

Not really.  I believe this has been mentioned on comp.std.c++,
but I did not succeed in finding the revelant articles with the
quick DejaNews search that I did.

But basically the relevant feature is templates and template
specialization.  Templates give you recursion at compile time,
and template specialization gives you the equivalent of if-then-else,
and that's about all you need.  I've included below an example which
computes factorials at compile time, using successor arithmetic in the
type system.  I believe it would be straight-forward, albeit tedious, to
extend this example to compute arbitrary recursive functions on natural
numbers.

The relevant part of the C++ standard is Annex B:

 |-1- Because computers are finite, C++ implementations are inevitably
 |limited in the size of the programs they can successfully process.
 |Every implementation shall document those limitations where known.
 |This documentation may cite fixed limits where they exist, say how to  
 |compute variable limits as a function of available resources, or say
 |that fixed limits do not exist or are unknown.
 | 
 |-2- The limits may constrain quantities that include those described
 |below or others. The bracketed number following each quantity is
 |recommended as the minimum for that quantity. However, these
 |quantities are only guidelines and do not determine compliance.
 ...
 |  * Recursively nested template instantiations [17].

Here's the example code.  Note that to compile this, you will
need a compiler that supports much more than 17 recursively
nested template instantiations.

// successor arithmetic:
struct Zero {
typedef Zero check_is_zero;
};
template class T struct Succ {
typedef T pred;
};
typedef SuccZero One;
typedef SuccOne Two;
typedef SuccTwo Three;
typedef SuccThree Four;
typedef SuccFour Five;

// some examples of recursion with if-the-else:
// addition
template class T1, class T2
struct Sum {
typedef typename Sumtypename T1::pred, SuccT2 ::t t;
};
template class T2
struct SumZero, T2 {
typedef T2 t;
};

// multiplication
template class T1, class T2
struct Prod {
typedef typename SumT2,
  typename Prodtypename T1::pred,T2::t::t t;
};
template class T2
struct ProdZero, T2 {
typedef Zero t;
};
typedef ProdTwo, Five::t Ten;
typedef ProdTwo, Ten::t Twenty;
typedef ProdTen, Ten::t Hundred;
typedef ProdTen, Hundred::t Thousand;

// factorial
template class T
struct Factorial {
typedef typename ProdT,
typename Factorialtypename T::pred::t::t t;
};
template 
struct FactorialZero {
typedef One t;
};

// equality
template class T1, class T2
struct ZeroIfEqual {
typedef typename ZeroIfEqualtypename T1::pred,
typename T2::pred::t t;
};
template 
struct ZeroIfEqualZero, Zero {
typedef Zero t;
};
template class T1
struct ZeroIfEqualT1, Zero {
typedef One t;
};
template class T2
struct ZeroIfEqualZero, T2 {
typedef One t;
};

// now some examples where the type-correctness of the program
// depends on the results of the arithmetic

// check that 2! == 2
typedef typename ZeroIfEqualtypename FactorialTwo::t, Two::t res;
typedef typename res::check_is_zero checkme;

// check that 5! == 120
typedef typename SumHundred, Twenty::t HundredAndTwenty;
typedef typename ZeroIfEqualtypename FactorialFive::t,
HundredAndTwenty::t res2;
typedef typename res2::check_is_zero checkme2;

-- 
Fergus Henderson [EMAIL PROTECTED]  |  "Binaries may die
WWW: http://www.cs.mu.oz.au/~fjh  |   but source code lives forever"
PGP: finger [EMAIL PROTECTED]| -- leaked Microsoft memo.





Re: Haskell 2 -- Dependent types?

1999-02-19 Thread Andrew Moran

Lennart Augustsson writes:

  OK, I'm curious.  Two people replied that C++ has undecidable type
  checking.  I was not aware of this (although I can't say I'm too
  surprised); do you have a reference?

 It's actually the template processing that can loop, but it is
 sort of part of the type checking.
 
 You can find an article in the POPL 99 proceeding about it.

Actually, I think Lennart means PEPM '99.  At least, there's an article called
"C++ Templates as Partial Evaluation" by Todd Veldhuizen (from the
wonderfully-named Extreme Computing Laboratory) which refers to this.  He
cites an example of using the templates to generate a list of prime numbers at
compile time due to Erwin Unruh (apparently discovered accidentally!).

Cheers,

Andy





how to exploit existential types

1999-02-19 Thread S.D.Mechveliani

Asking on existential types, i wrote 

 It is required to organise a table with the key
 data K = K1 | K2 | K3 ...
 to put/extract there the items of different types, say,  'a'  and 
 ('a','b')  as well.  Is this possible?
 Understanding nothing in this subject, i tried
  data KTab = forall a. KT (FiniteMap K a)
 [...]


I thank  Simon Marlow, Fergus Henderson, Jose Emilio Labra Gayo, 
 Pablo Azero, Koen Claessen, Christian Sievers

for the explanations. I am going to study them. 
Hm ... still try to escape :-)
Maybe, you can tell now simply: 
   have i a chance to simplify denotations with this?

For, Fergus Henderson  writes

 to put/extract there the items of different types, say,  'a'  and 
 ('a','b')  as well.  Is this possible?

 Yes.  
 But what do you want to do with the values once you've extracted them?



The particular question is: how to get free of extra constructors that
are used to organise a new type from several types?
Example.
  data Name = Meat | Vegetable | Vine  | ...deriving(Eq)

  data DMeat  = DMeat  {mName  :: String  -- ,...several fields
   } 
  data DVegetable = DVegetable { different fields }
  data DVine  = DVine  { different fields }
  ...
- 50 kinds of dishes, each described in individual manner
A program works with these dishes, modifying the values in these 
record fields.
But how to operate with Dinner-s?  
We assume a dinner may consist of arbitrary many dishes.

  type Dinner = [(Name,Dish)]

For this, we have to join the above dish-types to one new type

  data Dish = Meat' DMeat | Vegetable' DVegetable | ... -- 50 items

The new task is:  
  get from the dinner its meat part. If it is absent then put there
  such and such shashlyk.

  fixMeat :: Dinner - (Dinner, DMeat)
  fixMeatdn =
  case  lookup Meat dn
  of
Just (Meat' d) - (dn   , d)
_  - ((Meat,Meat' s):dn, s)
  where
  s = DMeat {mName = "shashlyk"}

We have here the parasitic constructors Meat', Vine'...
that have to "follow" the initial constructors  Meat , Vine ...,
otherwise we cannot get this all into one table.
And the pattern match in this `case':  Meat' is one of 50 
alternatives - i hope, it could match as fast as for 3 alternatives,
but this is certain exercise for the compiler developers.

With existentials, i hoped to achieve the effect of simplification,
something like  ...
Just d - (dn  , d)
_  - (s:dn, s)
where
s = DMeat {name = "shashlyk"...}
Is this possible?
If there is no chance, i would rather forget of existentials, so far.

Thanks a lot for the help.


--
Sergey Mechveliani
[EMAIL PROTECTED]








Re: Lists and FP (was Re: Functions allowing either 0 or 1 parameters?)

1999-02-19 Thread Shin-Cheng Mu

On Fri, 19 Feb 1999 01:19:18 -0500
Leon Smith [EMAIL PROTECTED] wrote:
 In this particular case, pretty much any Haskell compiler will
 automatically perform optimizations that will transform the first
 definition into the second definition.  So, the first definition will
 create the same object code as the second.  Even if the implementation
 doesn't optimize it, the fact that Haskell is lazy means that there isn't a
 huge difference between the two.  The following is how a implementation
 would reduce our un-optimized expression:

The instructive letter of Leon Smith advocated not only the use of lists,
but also the use of combinators on lists. I would like to ask a question
I have long in mind: to what extent can we trust compiler optimization?

2 examples I encountered recently are of particular interest to me. In
John Hughes' famous paper "Why Functional Programming Matters" 
he mentioned a function 'within' which takes a infinitely long list of 
approximations and returns the first element whose difference from
the previous element is smaller than a fixed epsilon:

within eps (x:y:xs) | abs (y-x)  eps = within eps (y:xs)
| otherwise   = y

I would like to code it in an alternative style:

within eps xs = (snd . head . (dropWhile (\(a,b) - abs(b-a)  eps))) (xs, tail xs)

Or, in one stage of a merge sort, I would like to merge every 2 elements
of a list (of lists). In recursive style it would be

ms [] = []
ms [xs] = [xs]
ms (xs:ys:xss) = merge xs ys : ms xss

It's also possible to rephrase it this way

ms xs = lzipWith merge (odds xs, evens xs)

where evens and odds returns the even and odd elements of a list respectively
and lzipWith is the "long" version of zipWith (which I think is something missing
in the standard library of Haskell... is it?).

I would say that the 2nd version of both example is the style I prefer and
would use to show off to my friend. But I hesitate to use them in productive
code because I do not know how clever the compiler is. Transforming the 2 
cases into their efficient counterparts involves many levels of deforestation
as well as inlining of pair or list operations ( patter matching the 2nd element
of a list). How much price must a compiler pay to perform all these transformation
on all functions in a large program? How much price we would pay if it does 
not do so?

I would like to know whether the state-of-the-art Haskell compilers are
able to handle these cases and how it is done other than massively
trying to deforest everything.

sincerely,
Shin-Cheng Mu
Academia Sinica, Taiwan.





Re: Haskell-2

1999-02-19 Thread Thomas Hallgren

Jose Emilio Labra Gayo wrote:

 
  I agree; Haskell 2 should have existential (and universal) types.  I
  also think it should have both extensible records and extensible
  variants.  (See the following paper for more information on these.
  TREX is an implementation of half of this system; it has the
  extensible records but not extensible variants.)
 
  Carl Witty
  [EMAIL PROTECTED]
 
 Just a question, Is there anyone trying to implement extensible variants?

Johan Nordlander has developed a type system which allows subtyping on both
records and variants, at the same time as it stays very close in spirit to
the convetional Hindley/Milner types system. It is described in a ICFP'98
paper. You can get it from

http://www.cs.chalmers.se/~nordland/

There is also ongoing work on an implementation of a version of Haskell,
called OHaskell, which incoropates this type system.

--
Mvh Thomas H








RE: Haskell 2 -- Dependent types?

1999-02-19 Thread Nick Kallen

 I'm curious: how many people have actually written a program in
 Cayenne?  How many people have written programs that made significant
 use of the dependent typing?  Has anybody tried to teach a programming
 class using Cayenne?

I'll admit to not having yet written something in Cayenne, but I'm an
adamant supporter of adding dependant types to the language. I remember a
year ago, I was writing a small (trivial) program. One of the essential ways
I was structuring the program was with a function "apply" similar to
Lisp/scheme's apply. Needless to say, you can't express apply in Haskell
although you can in Cayenne. In the context of this problem, I could easily
get around this by restructuring my program, but this was obviously not
ideal. We should be able to express trivial functions like apply in the type
system.

 apply f (p:ps) = apply (f p) ps
 apply f [] = f

I wanted to express the type as something like:

 apply :: (a - a - ... - a) [a] - a

The stated domain of apply is much larger than its actual domain. I want its
domain to be:

a function whose arity is the length of the second parameter (a list).

It's clear that the precise domain of apply can only be expressed with a
function.

I would like to say that the type of the first parameter is applyType:

applyType a [] = a
applyType a (p:ps) = a - applyType a ps

I presume the type of the applyType is then

applyType :: (a :: #) - [a] - #

with # being the type of all types.

Thus apply is of type

apply :: (applyType a l) (l :: [a]) - a

Now there are a ton of problems with what I just stated.

1) The type of apply is somewhat ambiguous. The a passed to applyType is
free.
Assumption: free variables are universally quantified. This is consistent
with Haskell's current notation for typing.

2) This isn't valid Cayenne (I'll get to this later)

3) The type of applyType can be more specific.
Recall,

applyType :: (a :: #) - [a] - #

The final # is actually just function space.

How would we express the notion of a function space? Well, lets start with
the simpler problem of defining the n-function space (my vocabulary is
obviously falling apart at this point).

F :: (a :: #) Integer - #
F a 0 = a
F a n = a - (F a (n - 1))

We however want to generalize this... I'm not quite sure how to describe it,
but I'll do the following:

F a * = member (map (F a) [0..]) // member [a] a - Bool

so applyType is then

applyType :: (a :: #) - [a] - (F a *)

and applyType can be defined more succinctly:

applyType a l = F a (length l)

and since the recursion has been eliminated from applyType, you can eschew
applyType altogether and type apply thusly:

apply :: (F a (length l)) (l :: [a]) - a

This is satisfactory, but a reasonable request is to make the *range* of
apply even more general. Since apply's first parameter is a curried
function, it seems to me that there's no reason why the range of apply can't
also be a function. That is,

apply should return a value of type a iff the length of its second parameter
equals the arity of its first. Otherwise, the length of the second must be
less than the arity of the first, in which case apply should return a
function whose arity is the difference of the arity first parameter and the
length of the second.

Example:

apply (+) [1] == \x - 1 + x

so one now expresses the type of apply thusly:

apply :: (F a *) (l :: [a]) - (F a *).

This isn't completely satisfactory, since the first parameter of apply and
the range are now too general.

To make them specific, I define the following:

arity :: (F a *) - Int
arity (a - as) = 1 + (arity as)
arity a = 0

Fr a min max = member (map (F a) [min..max])

so apply is now typed

apply :: (f :: (Fr a [(length l)..])) (l :: [a])
- (F a ((arity f) - (length l)))

whew.

Now I must warn you that I'ven't checked anything at all, so it is highly
probable that there are errors. Like, I'm introducing things like pattern
matching on the function type constructor (-). I'm not sure if this is
valid.

Some questions for Lennart (and those more knowledgeable than I):

[1] What type can Cayenne infer for apply just given apply's definition?
[2] I know my last type for apply is invalid cayenne due to the order of
parameters and such, but if it's massaged a little bit: can Cayenne type
check it?


Foremost is that dependant types allow us to type more things than before.
The example I've shown demonstrates that even a simple thing like apply
needs them. One might infer, then, that there are possibly many simple and
perhaps common things which require this sort of type system.

It is also clear, however, that dependant types are no trivial thing.
Expressing the most general type of apply--that's not a super-type--is a
complicated process. It is clear that a large library of type functions will
likely be necessary, I think. This can be used as an argument both for and
against dependant types.

It is, however, also clear that when in using dependant types, much more
type 

Do Existential Types make Algebraic Types obsolete? (was Re: how to exploit existential types)

1999-02-19 Thread S. Alexander Jacobson

Do existential types makes algebraic types obsolete?
I mean there seems to be a large semantic overlap between the two
concepts.

For example, once you can implement lists with just the product type (,),
why bother with algebraic types?

Arguably Boolean is a natural algebraic type, but if we pattern
match on typenames then we don't need the algebraic types here. e.g.

 --Booleans w/o algebraic types
 data True = True 
 data False = False
 class Boolean where -- no methods required
 instance Boolean True where -- trivial implentation
 instance Boolean False where --trivial implementation
 --(There is probably much better syntax for this)

Pattern matching on type names would not be a violation of the type
system, it would just be syntactic sugar...e.g. for booleans it would be
equivalent to:

 --Hack because there is no built in pattern matching on type names
 instance TypeName True where
  typeName x = "True"
 instance TypeName False where
  typeName x = "False"
 --definition of if' in this framework
 if' x y z = case (typeName x) of
   "True" - y
   "False" - z

Languages like C and Java do not seem to have an equivalent to algebraic
types because they allow heterogenous lists.  

Are there contexts where you need algebraic types because existential
types won't do the job?  Wouldn't everybody be happier if you could just
pattern match on type names (someone else requested this in a recent
thread)?

--
Or the most extreme version of this question, once you abandon algebraic
types, do you need constructor names at all or can you just use
position e.g.

 data MyType a b = Int a b
 myFunc (MyType x y z) = MyType (x+1) y z
 data MyType2 a b = {field1::Int,field2::a,field3::b}
 myFunc2 x = (field1 x+1,field2 x)

-Alex-


On Fri, 19 Feb 1999, Michael Hobbs wrote:

 "S.D.Mechveliani" wrote:
  With existentials, i hoped to achieve the effect of simplification,
  something like  ...
  Just d - (dn  , d)
  _  - (s:dn, s)
  where
  s = DMeat {name = "shashlyk"...}
  Is this possible?
  If there is no chance, i would rather forget of existentials, so far.
  
  Thanks a lot for the help.
 
 I'm not sure if this is a real world problem, or just a for-instance.
 (You never know! :) Anyway, I can see that fundamental issue that you
 want to resolve is how to store various types of data into a single
 list. The issue of figuring out the type of each element is is resolved
 by the `Name' stored with each element. I don't know much yet about
 existential types, but I would think that you would still have to have
 some function or something that relates `Name's to particular types.
 
 But my real point in replying to this message is to see if you actually
 need a multi-type list. Do you really *need* to have separate types for
 DMeat, DVine, etc.? For example, instead of having:
 
   data DMeat  = DMeat  {mName  :: String  -- ,...several fields
} 
   data DVegetable = DVegetable { different fields }
   data DVine  = DVine  { different fields }
   ...
   -- 50 kinds of dishes, each described in individual manner
   data Dish = Meat' DMeat | Vegetable' DVegetable | ... -- 50 items
 
 would it be possible to use:
 
   data Dish = DMeat {mName :: String, ...}
 | DVegetable {...}
 | DVine {...}
 | ...
 
 This would eliminate the need to have a multi-type list, for this
 particular example anyway.
 
 - Michael Hobbs
 

___
S. Alexander Jacobson   Shop.Com
1-212-697-0184 voiceThe Easiest Way To Shop











Re: Haskell-2

1999-02-19 Thread Jose Emilio Labra Gayo

 
 I agree; Haskell 2 should have existential (and universal) types.  I
 also think it should have both extensible records and extensible
 variants.  (See the following paper for more information on these.
 TREX is an implementation of half of this system; it has the
 extensible records but not extensible variants.)
 
 Carl Witty
 [EMAIL PROTECTED]
 
Just a question, Is there anyone trying to implement extensible variants?

I can simulate them with the "Subtyping" trick of S. Liang, P. Hudak, M. 
Jones [1], but I am not very happy with that solution.

Regards, Jose E. Labra

[1] S. Liang, P. Hudak, M. Jones, Monad transformers and modular 
interpreters, POPL'94: 21st ACM SIGPLAN-SIGACT Symposium on Principles of 
Programming Languages, San Francisco, California (1995).