2 bugs in ghc-4

1998-10-26 Thread S.D.Mechveliani

Since there occurred problems with e-mail delivery, i am sorry,
i repeat the two bug reports for   ghc-4-i386-linux.

--
Sergey Mechveliani
[EMAIL PROTECTED]



*
1. The reduced `panic' example:ghc -c Bug.hs

ft  does not look natural. But after `panic' is fixed, i hope the 
original program will work.
By the way, has 
   class PolLike p  where  cPMul :: Eq a = a - p a - p a

sense? I thought, yes.


---
class PolLike p  where  cPMul :: Eq a = a - p a - p a

class Eq a = AddSemigroup a  where  add :: a - a - a

type UMon a =  (a, Integer  )  
type Monomial a =  (a, [Integer])   
data UPol a =  UPol [UMon a] a String [a]

instance Eq a = Eq (UPol a)   

instance PolLike UPol  where  cPMul _ _ = error ""  

instance Eq a = AddSemigroup (UPol a)


ft :: AddSemigroup k = UPol k - [UPol k]

ft  f@(UPol _ c v d) = 
  let
berl h =  let  b  = [cPMul c h] 
   fr = map (const []) [cPMul c h] 
  in 
   case  head fr
   of  
 _:_ - let  es = map (add (UPol [] c v d)) [h]
in   berl h
  in
  berl f





*
2. Modularity bug:

-
module T1 where
type Z = Integer
toZ= toInteger  :: Integral a = a - Z

-- the idea is to switch Z, toZ between Integer, Int
-
module Main where
import List (genericTake)
import T1   (Z, toZ )

f :: Z - Z - [Z] 
fni =  case  toZ i  of  j - genericTake (n+j) (repeat n)

main = let  ns = f 2 3  in   putStr (shows ns "\n")
-


After   ghc -c T1.hs,  ghc -c Main.hs   

the compiler derives a contradiction for  i :: Int,  Z.

After moving the definition of toZ  to Main.hs the compiler solves
the types differently.




modularity bug?

1998-10-26 Thread S.D.Mechveliani

Lenart was right.
I am sorry, indeed,   toZ :: Integral a = a - Z
  toZ = toInteger  
helps. I recalled, exactly this was the initial bug program.
But sorry, probably, i had confused something.


Still, why moving   toZ = toInteger  :: Integral a = a - Z

to another module (Main.hs) changes the compilation success?


-
module T1 where
type Z = Integer
toZ= toInteger  :: Integral a = a - Z   
-
module Main where
import List (genericTake)
import T1   (Z, toZ )
f :: Z - Z - [Z] 
fni =  case  toZ i  of  j - genericTake (n+j) (repeat n)

main = let  ns = f 2 3  in   putStr (shows ns "\n")
-



Also i used to read "probably...monomorphism restriction..." in ghc 
report, and then to impove the code. This time, the report is not so
easy to understand:
Couldn't match `Int' against `Z'
Expected type: Int
Inferred type: Z
In the first argument of `toZ', namely `i'
In the scrutinee of a case expression: toZ i



--
Sergey Mechveliani
[EMAIL PROTECTED]








Re: modularity bug?

1998-10-26 Thread Lennart Augustsson


 Lenart was right.
 I am sorry, indeed,   toZ :: Integral a = a - Z
   toZ = toInteger  
 helps. I recalled, exactly this was the initial bug program.
 But sorry, probably, i had confused something.
 
 
 Still, why moving   toZ = toInteger  :: Integral a = a - Z
 
 to another module (Main.hs) changes the compilation success?
Because if you have toZ where it is being used then the
monomorphic type it gets is the one it needs to have.
Whereas, if it is exported, the default mechanism decides the type.

-- Lennart



Re: monad type errors in class definition?

1998-10-26 Thread Pablo E. Martinez Lopez

  class MetaData a where
   constructorName::a-String
   mapArgs::(MetaData b,MonadPlus c) = (b-c)-a-[c]
 
 results in the error
 Illegal type "[c]" in constructor application
 
 If I replace MonadPlus with Show or Num there is no error.
 (Replacing MonadPlus with Monad also result in an error)
 
 What is so special about MonadPlus and Monad that they result in an error,
 but Show or Num don't.

The problem is that MonadPlus expects a type constructor and Show
expects just a type.
As your variable c is not applied in the right hand side, it is
considered to be a variable for a type, and not for a type constructor.
You should say something as

mapArgs::(MetaData b,MonadPlus c) = (b-c a)-a-[c a]

or similar.
In the paper 

Functional Programming with Overloading and Higher-Order Polymorphism,
Mark P. Jones, First International Spring School on Advanced Functional
Programming Techniques, B{\aa}stad, Sweden, Springer-Verlag Lecture
Notes in Computer Science 925, May 1995.

you can find a very good explanation of this stuff (about kinds, and
kind inference). It is available at
http://www.cs.nott.ac.uk/~mpj/springschool.html

Fidel.





Re: topdelcs / decls

1998-10-26 Thread Johannes Waldmann

Felix Schroeter wrote:

 newtype IntFunnilyOrdered = IFO Int
 instance Ord IntFunnilyOrdered where compare ...
 int_from_ifo (IFO x) = x

   map int_from_ifo $ sort $ map IFO l

 Ideally, the compiler should figure out that map IFO and map
 int_from_ifo are essentially noops, except changing the class
 instances to use.

right. but i'd like to have an even more clever compiler,
in order to not have to write all those type coercions explicitely.

 If you use the instances once, I think using something like sortWith
 instead will be more elegant.

it depends. the design question then is 
how to pass the argument (=) to sort: 
visibly (sortBy) or invisibly (as an Ord instance).

 foo = let 
 instance Ord T where compare ... = ... 
   in 
 sort (something::[T])

 There's no Ord instance visible in the definition of sort.

i think there is (or should be). we have two different meanings of T here:
one is just T, the other is T with the Ord instance.
the last one should apply for the declaration of `something'
(because it is visible at that point).

perhaps this should better be written as
"type T' is instance Ord T where ..."

 somelist :: [T]
 somelist = let instance Ord T where ... in (generate some list of values in T)

the Ord instance here is local, and thus not available later in the program.

 sortedlist :: [T]
 sortedlist = let instance Ord T where [different from the above instance] in
   sort somelist

somelist's type is implicitely propagated from "just T" to
"T with the instance decl just given".
alternatively, we could require explicit propagation.

 That somehow twists my mind :-)

indeed, i'm not saying the proposal is fully thought out,
or easily implementable. 

-- 
Dr. Johannes Waldmann Institut fur InformatikUniversitat Leipzig
[EMAIL PROTECTED] http://www.informatik.uni-leipzig.de/~joe/
Augustusplatz, D-04109 Leipzig, Germany, Tel/Fax (+49) 341 97 32 204/209





Re: Haskell 98

1998-10-26 Thread Hans Aberg

At 14:15 + 98/10/24, Simon Marlow wrote:
Simon Peyton-Jones [EMAIL PROTECTED] writes:

 Consider the function

  t :: T a = T a - T a

 I think that it's far from clear what each of the T's mean!
 Worse, in Haskell 2 we'll also have

  t :: T T = T a - T a

 In (T T) one is class and the other is a type constructor.

I'm not convinced by the argument "this allows you to write obfuscated
Haskell".  After all, Haskell is already a wonderful language for
writing obfuscated code; eg. what does the following definition mean

   f f = f

is it a static error (re-use of 'f'), a type error, or a definition of
the identity function?  (it's the latter).

Here's to cleaning up the language, and to more exciting obfuscated
Haskell competitions!

  Haskell translates  f f = f  into  f := f |- f; on the right hand side
"f" is a bound variable, on the left hand side "f" is a name. Suppose I
inidicate variables with a slash, then the formula would read
f := \f |- \f
or f(\f) := \f.

  So Haskell allows different logical entities have the same name dependent
on the context, which causes the confusion.

  Now, I think the problems you have with the original discussion is that
you fail to properly define the underlying semantics, specifically, the
general principles on which it depends.

  Hans Aberg
  * Email: Hans Aberg mailto:[EMAIL PROTECTED]
  * Home Page: http://www.matematik.su.se/~haberg/
  * AMS member listing: http://www.ams.org/cml/






Re: Haskell 98

1998-10-26 Thread Philip Wadler

 Consider the function
 
   t :: T a = T a - T a
 
 I think that it's far from clear what each of the T's mean!
 Worse, in Haskell 2 we'll also have
 
   t :: T T = T a - T a
 
 In (T T) one is class and the other is a type constructor.

Let's leave the language as it is: class names and type names must be
distinct.  Rationale: the above examples show that a change might have
questionable consequences.  Recall that the change requires adding the
label `class' to signatures, but not adding the label `type'; it feels
more like a convenient hack than a well-rounded design.  Rather than
make a questionable change now, let's leave it for Haskell 2 and get it
right there.  -- P





Re: Haskell 98

1998-10-26 Thread Hans Aberg

At 14:30 + 98/10/26, Peter Thiemann wrote:
 Haskell translates  f f = f  into  f := f |- f; on the right hand side
"f" is a bound variable, on the left hand side "f" is a name. Suppose I
inidicate variables with a slash, then the formula would read
 f := \f |- \f
 or f(\f) := \f.

I don't really understand your remark. f f = f  as a toplevel
definition is equivalent to (in this special case)

letrec ...
   f = \f - f
   ...

  I just avoid using Haskell notation in order to not get the notation
confused as Haskell does.

It's not different logical entities, all occurrences of f are variables.

  Different occurrences of f have different semantic meaning (that is, the
"f" in one place is not the same as the "f" in another place).

It's not Haskell that's causing the confusion if any, it's the lambda
calculus, more precisely: alpha-conversion.

  The original question was this: What is the meaning of "f(f) = f"? I
remarked that in this case Haskell has a very good strategy, namely
interpreting it as the expression f := f |- f, or "f is assigned the
expression  lambda f f" if you so want; the lack of such a good strategy
seemed to cause the other problems discussed in this thread.

  Otherwise, the naming of functions is not part of the lambda calculus;
one must add an interpretation of this lambda calculus in order to arrive
at a meaning of an assignment in the computer sense. (For example, if I
define \f to denote a free variable, I could assign f := \f + 1, and later
bind this \f by the assignment f := \f |- f, which would work out to the
increment function. In this example, free variables and symbol table names
have a distinctly different behavior.)

  Hans Aberg
  * Email: Hans Aberg mailto:[EMAIL PROTECTED]
  * Home Page: http://www.matematik.su.se/~haberg/
  * AMS member listing: http://www.ams.org/cml/






Re: Fixing imports for and namespaces (was: Simon's H98 Notes)

1998-10-26 Thread David Barton

One more quick comment, and then I think I (at least) am done (to the
extent that the difference in opinion is clearly defined).

Fergus Henderson writes:

And, again IMHO, it is the task of the language to *define* the
encapsuation (or to allow that encapsulation to be defined), and
the job of the operating system or programming environment to
enforce it (or to trust to convention, depending).

   There's not much difference between "language implementation" and
   "programming environment", is there?

No; however, there is a world of difference between "language
implementation" and "language definition".  The two are *very*
distinct in my mind.  Note that I said (above) the job of the language
is to define; you morphed that into "language implementation".

   Above you say it is the job of the OS or programming environment to
   enforce encapsulation.  I think it should be the language
   implementation's job, but the OS should be considered a part of the
   language implementation, so letting the OS handle it would be one
   way for the language implementation to do the enforcement.

I am happy to make it part of the language implementation as long as
it does not impinge on the language definition, leaving other
implementations free to do it other ways.  Pragmas may be one way to
do this.  I simply object (and will continue to object) to making one
mechanism of encapsulation enformement part of the definition,
imposing it on all implementors.  To repeat: defining the
encapsulation is the job of the language defintion, but enforcing it
is not (and should not be).  All IMHO, of course.

Dave Barton *
[EMAIL PROTECTED] )0(
http://www.averstar.com/~dlb





type error, why?

1998-10-26 Thread S. Alexander Jacobson

I wrote the following function that attempts to generalize show by
allowing the user to choose the function to stringify constructor
arguments.

 stringArgs' sep stringer1 (MyFoo x i s) = 
x' ++sep++i' ++ sep ++ s'
  where 
   x'=stringer' x
   i'=stringer'' i
   s'=stringer''' s
   stringer' o=stringer o
   stringer'' o=stringer o
   stringer''' o =stringer o
   stringer o=stringer1 o --!! replacing stringer1 w/ show works!

This function generates a type error because stringer is being used as
Int-Char and as Char-Char.  But, if I replace stringer1 in the last
line, with the function `show`, hugs allows this function.

However, if I use show and attempt to call this function using foo:

 foo x = stringArgs "\n" show (MyFoo "asd" 12 "asd")

I get an ambiguous type signature error.

What am I doing wrong?

-Alex-

___
S. Alexander Jacobson   i2x Media  
1-212-697-0184 voice1-212-697-1427 fax





Re: type error, why?

1998-10-26 Thread Peter Thiemann

 "Alex" == S Alexander Jacobson [EMAIL PROTECTED] writes:


Alex I wrote the following function that attempts to generalize show by
Alex allowing the user to choose the function to stringify constructor
Alex arguments.

 stringArgs' sep stringer1 (MyFoo x i s) = 
 x' ++sep++i' ++ sep ++ s'
 where 
 x'=stringer' x
 i'=stringer'' i
 s'=stringer''' s
 stringer' o=stringer o
 stringer'' o=stringer o
 stringer''' o =stringer o
 stringer o=stringer1 o --!! replacing stringer1 w/ show works!

Alex This function generates a type error because stringer is being used as
Int- Char and as Char-Char.  But, if I replace stringer1 in the last
Alex line, with the function `show`, hugs allows this function.

OK, show :: forall a . Show a = a - String [if my memory serves correctly]
so it is polymorphic in the type a.
However, the parameters of a function cannot (currently) have a
polymorphic type. So when you want to pass show to stringArgs you will 
have to use one particular instance of this type. In the present case, 
you get Show a = a - String [note that the forall is gone], but you
cannot resolve the overloading because you do not know what a is. Hence

Alex However, if I use show and attempt to call this function using foo:

 foo x = stringArgs "\n" show (MyFoo "asd" 12 "asd")

Alex I get an ambiguous type signature error.

the ambiguity. If Haskell included first-class polymorphism (which is
on the list for Haskell 2 and which is present in some form in Hugs
1.3c) and you provided an explicit signature, then your function and
your example would work out. Modulo syntax, this is what is would look 
like:

stringArgs' :: String - (forall a . Show a = a - String) - MyFooType - String
stringArgs' sep stringer (MyFoo x i s) =
x' ++sep++i' ++ sep ++ s'
  where 
x'=stringer x
i'=stringer i
s'=stringer s

And your function call would look just like the one above.

-Peter





Re: type error, why?

1998-10-26 Thread S. Alexander Jacobson

In other words, you are saying that I want a feature, first class
polymorphism, that is now available in Hugs1.3c and from the docs,
GHC4.0?.

Since I am doing development in Hugs 1.4, I guess the question is when
will Hugs1.4  have this feature and is this feature
compatible with Derive?

Alternatively, since GHC 4.0 is there a way to run just the type-checker
part of GHC 4.0 without waiting for it to compile everything?

Also, has anyone manageed to build GHC4.0 for win32?

-Alex-

___
S. Alexander Jacobson   i2x Media  
1-212-697-0184 voice1-212-697-1427 fax


On Mon, 26 Oct 1998, Peter Thiemann wrote:

  "Alex" == S Alexander Jacobson [EMAIL PROTECTED] writes:
 
 
 Alex I wrote the following function that attempts to generalize show by
 Alex allowing the user to choose the function to stringify constructor
 Alex arguments.
 
  stringArgs' sep stringer1 (MyFoo x i s) = 
  x' ++sep++i' ++ sep ++ s'
  where 
  x'=stringer' x
  i'=stringer'' i
  s'=stringer''' s
  stringer' o=stringer o
  stringer'' o=stringer o
  stringer''' o =stringer o
  stringer o=stringer1 o --!! replacing stringer1 w/ show works!
 
 Alex This function generates a type error because stringer is being used as
 Int- Char and as Char-Char.  But, if I replace stringer1 in the last
 Alex line, with the function `show`, hugs allows this function.
 
 OK, show :: forall a . Show a = a - String [if my memory serves correctly]
 so it is polymorphic in the type a.
 However, the parameters of a function cannot (currently) have a
 polymorphic type. So when you want to pass show to stringArgs you will 
 have to use one particular instance of this type. In the present case, 
 you get Show a = a - String [note that the forall is gone], but you
 cannot resolve the overloading because you do not know what a is. Hence
 
 Alex However, if I use show and attempt to call this function using foo:
 
  foo x = stringArgs "\n" show (MyFoo "asd" 12 "asd")
 
 Alex I get an ambiguous type signature error.
 
 the ambiguity. If Haskell included first-class polymorphism (which is
 on the list for Haskell 2 and which is present in some form in Hugs
 1.3c) and you provided an explicit signature, then your function and
 your example would work out. Modulo syntax, this is what is would look 
 like:
 
 stringArgs' :: String - (forall a . Show a = a - String) - MyFooType - String
 stringArgs' sep stringer (MyFoo x i s) =
   x' ++sep++i' ++ sep ++ s'
   where 
 x'=stringer x
 i'=stringer i
 s'=stringer s
 
 And your function call would look just like the one above.
 
 -Peter
 






Re: type error, why?

1998-10-26 Thread Peter Thiemann


Alex In other words, you are saying that I want a feature, first class
Alex polymorphism, that is now available in Hugs1.3c and from the docs,
Alex GHC4.0?.

Yes.

Alex Since I am doing development in Hugs 1.4, I guess the question is when
Alex will Hugs1.4  have this feature and is this feature
Alex compatible with Derive?

As far as I know, the Hugs 1.4 folks are working on it. Derive is only 
a preprocessor for data type declarations, I don't know whether it
works with existentially typed or polymorphic constructor
arguments. If you don't have these, then I don't see any problems.

Alex Alternatively, since GHC 4.0 is there a way to run just the type-checker
Alex part of GHC 4.0 without waiting for it to compile everything?

Alex Also, has anyone manageed to build GHC4.0 for win32?

Sorry, beats me.

-Peter





Re: topdelcs / decls

1998-10-26 Thread Michael Hobbs

Felix Schroeter wrote:
  for instance, i could want to sort a list,
  according to two different criteria,
  using two different instances of Ord.
 
 newtype IntFunnilyOrdered = IFO Int
 instance Ord IntFunnilyOrdered where
   compare (IFO x) (IFO y) | even x  even y = compare x y
   | even x  odd y  = LT
   | odd x  even y  = GT
   | otherwise= compare x y
 int_from_ifo (IFO x) = x
 
 newtype IntReverse = IR Int
 instance Ord IntReverse where
   compare (IR x) (IR y) = compare y x
 int_from_ir (IR x) = x
 
 Now, you can do
   map int_from_ir $ sort $ map IR l
 or
   map int_from_ifo $ sort $ map IFO l

Trust me, if you have more than just a few ways to order, this method
gets real complicated real fast. You have to keep track of which list is
based on which 'newtype' and then constantly convert the newtype
back-and-forth to/from the original type when you add or retrieve an
element. The 'map' trick is a nifty work-around for this particular
instance, but it doesn't work well in general for "Bag" ADTs. That is
because the resulting list has lost all of its sorting information. In
order to insert a new element, the list would have to be converted back
into the newtype, insert the element, then convert list back to original
type. I'll be honest and admit that I haven't thought real hard about
how much the efficency will be affected by constantly mapping
back-and-forth with lazy evaluation, but my gut feel is that the
overhead of such a scheme will be expensive for any large Bag.





Re: Haskell 98

1998-10-26 Thread Peter Thiemann

 "Hans" == Hans Aberg [EMAIL PROTECTED] writes:

 It's not different logical entities, all occurrences of f are variables.

Hans   Different occurrences of f have different semantic meaning (that is, the
Hans "f" in one place is not the same as the "f" in another place).

All I'm saying is in "f f = f", the first occurrence of f is a binding
occurrence, the second one is also a binding one, and the third one is 
an occurrence of f bound to the second binding.

 It's not Haskell that's causing the confusion if any, it's the lambda
 calculus, more precisely: alpha-conversion.

Hans   The original question was this: What is the meaning of "f(f) = f"? I
Hans remarked that in this case Haskell has a very good strategy, namely
Hans interpreting it as the expression f := f |- f, or "f is assigned the
Hans expression  lambda f f" if you so want; the lack of such a good strategy
Hans seemed to cause the other problems discussed in this thread.

There is no assignment in "f f = f", it's just binding of names. Using 
any notion of assignment in this context is misleading IMHO.

Hans   Otherwise, the naming of functions is not part of the lambda calculus;

I disagree on that one: the meaning of 

letrec f = \f - f in e
is
(\f - e) (fix \f - \f - f)

[plug in any fixpoint combinator for fix]

-Peter