`Funny global thing' in ghc-4

1998-11-09 Thread S.D.Mechveliani

Please, what the folowing `Funny global thing' might mean in  ghc-4 ?

make source/pol/factor/Pfact0_.o
 /usr/ghc/4/bin/ghc -c source/pol/factor/Pfact0_.hs -fglasgow-exts  
 -optC-fallow-overlapping-instances -optC-fallow-undecidable-instances  
 -fvia-C 
 -K1500k -syslib misc -cpp -recomp -hi-diffs -iexport -Iexport 
 -odir export -fno-warn-overlapping-patterns -ohi export/Pfact0_.hi  
 -H1k  -Onot

ghc: module version changed to 1; reason: no old .hi file
Funny global thing?: cdX7_btm:
Funny global thing?: cdZf_btm:


--
Sergey Mechveliani
[EMAIL PROTECTED]




Re: `Funny global thing' in ghc-4

1998-11-09 Thread Jan Laitenberger



Your question was already on the mailing list before:

Simon Marlow wrote:
 This means you've got a pretty complex bit of code that needed a
 bitmap with more than 32 entries to describe a stack frame.

 Cool :-)

  I wrote:
   can the "Funny global thing?" message be ignored? 
  (It does not crash the compiler.)

Simon Marlow wrote:
 Yep, the warning can be ignored.


Best wishes,

Jan

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



RE: GHC-3.03-current bugs

1998-11-09 Thread Sigbjorn Finne (Intl Vendor)


Sven Panne [EMAIL PROTECTED] writes: 
 
  ...
 
 But something really strange is going on here:
 
 -- Foo.hs -
 module Foo where
 malloc :: IO Int
 malloc = _casm_ ``%r = 42;''
 
 -- Bar.hs -
 module Bar where
 import Foo
 blah :: IO Int
 blah = malloc
 
 ---
 panne@liesl:/tmp  ghc -O -funfold-casms-in-hi-file 
 -fglasgow-exts -c Foo.hs -o Foo.o
 ghc: module version changed to 1; reason: no old .hi file
 panne@liesl:/tmp  ghc -O -funfold-casms-in-hi-file 
 -fglasgow-exts -c Bar.hs -o Bar.o -dshow-passes
 *** Reader:
 *** Renamer:
 
 panic! (the `impossible' happened):
   IdInfo parse failed malloc
 

Thanks for a fine report, sorry for taking so long in replying.
It's a buglet, which somehow managed to get past our entire
ISO 9001 Quality Assurance Department. Fixed.

--Sigbjorn




RE: H/Direct-0.12 buglets

1998-11-09 Thread Sigbjorn Finne (Intl Vendor)


Sven Panne [EMAIL PROTECTED] writes: 
 
 To install H/Direct-0.12 on Linux, two things had to be changed:
 
* Move an #include to a more probable place (just guessing...):
 

Thanks, the fix was almost right, the "comPrim.h" include should
appear inside the __CYGWIN32__ #ifdef, since it's a replacement
header file that allows us to continue using gcc/egcs.

 
 Some remarks regarding the examples:
 
* [pure]int rand(void); ???
  I really hope that rand is *not* a pure function...  :-}
 

thx, fixed.

* int strncmp([in,string]char* s1,[in,string]char* s2,[in]int n);
  Shouldn't this read:
  int strncmp([in]FastString s1,[in]FastString s2,[in]int n);

Yep, that would make it more useful.

--Sigbjorn




Re: Haskell 98 progress

1998-11-09 Thread Alex Ferguson


Hi Simon, you spake of simple-context restriction:
   My default position is not to change.  Question: who, apart from
   Ralf, has actually tripped over the lack of contexts of the
   form (C (a t1 .. tn)) in Haskell 1.4?

*raises hand and jumps up and down*  Me, mememe!  I provided you
with an example of this many moons ago (unless I'm going crazy(ier)).

I'm moderately agog at your default default: it _only_ restores
principal types and fixes some programs, so that's not a big
enough reason to do it?  OK, that's a tad unfair.  But assuming
you can show the change is at any rate sound, then at worst it's a
conservative, harmless extension, unless I'm missing something huge
and vast and horrible (never unlikely).

Slan,
Alex.






RE: MonadZero (concluded)

1998-11-09 Thread Hans Aberg

At 01:58 -0800 1998/11/09, Simon Peyton-Jones wrote:
Following many protests, the right thing to do seems
to be to move MonadPlus to the Monad library.  Specifically:

   class Monad m = MonadPlus m where
 mzero :: m a
 mplus :: m a - m a - m a

  It seems me that the MonadPlus is just a monad whose algebras are
monoids. So perhaps it should be renamed to reflect that fact.

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







A short study of fuzzy oscillator

1998-11-09 Thread Jan Skibinski


I have posted a literate Haskell module "Fuzzy_oscillator"
in our collection of Haskell modules:
http://www.numeric-quest.com/haskell/
You may also download it as a gzipped bundle (containingg 9 plots)
according to downloading instructions on that page.

Credits go to Gary Meehan and Mike Joy from University of warwick
for their module Fuzzy.hs.
 
Summary
---

This module presents a short study of one-degree-of-freedom (1DOF)
oscillator subjected to resonant sinusoidal excitation force and
whose vibrations are controlled by a family of fuzzy controllers:

+ Velocity controller
+ Displacement controller
+ Displacement-velocity controller

Haskell simulations demonstrate that each controller performs
extremely well -- reducing resonant amplitudes to comparatively
small values, even though none of the controllers is thoroughly
tuned and our choice of kinematic fuzzy subsets is very
simplistic.
This suggests that fuzzy logic offers very powerful tools to
vibration control engineers; no special skills for solving
nonlinear equations are required and purely experimental approach
would suffice to design good controllers for such applications.

The obvious physical realizations of fuzzy controllers
are active devices that employ sensors, processors
and actuators. Less appreciated is, however, fact that traditional
passive control -- such as dry friction, viscous damping,
nonlinear springs or snubbers -- can be also modeled by fuzzy logic.


Jan







RE: MonadZero (concluded)

1998-11-09 Thread Simon Peyton-Jones


Following many protests, the right thing to do seems
to be to move MonadPlus to the Monad library.  Specifically:

class Monad m = MonadPlus m where
  mzero :: m a
  mplus :: m a - m a - m a

filterM :: MonadZero m = (a - m Bool) - [a] - m [a]
guard   :: MonadZero m = Bool - m ()
mfilter :: MonadZero m = (a - Bool) - m a - m a
concatM :: MonadPlus m = [m a] - m a


Alex, you'll have to use `mplus` instead of (++); or you 
can define a new operator (+++) to mean `mplus`; or you can
hide the list (++) and redefine it to be `mplus`.

I guess that 95% of the mailing list is tired of MonadZero.
If anyone has further thoughts, pls send them to me only
(and, of course, any other individuals you like).

Simon





Re: derive conflicts with multiply-defined and module level import

1998-11-09 Thread S. Alexander Jacobson

On Sat, 7 Nov 1998, Fergus Henderson wrote:
  Well, it depends on what you call *strong*. The only reason that I heard is
  that it prevents users from making possibly unwanted errors.
 
 Another reason is that allowing definitions to be split up
 without any special syntax indicating this would harm readability.
 If I see a definition, I can't be sure it's complete without
 examining the whole module.

I am very sympathetic to readability arguments, but I also agree with erik
that programmers should have a way out when necessary.  Code generation is
one of those cases where one can sacrifice readability.

In that context, your proposal

 to allow them to be separated, but only
 with some special declaration, e.g. a keyword "noncontiguous",
 prefixed to each clauses, that wouldn't be so bad for readability.

Would be something that I agree with.

 But if we have to add new syntax to make it work then it
 is getting to be more trouble than its worth.

Since the application is code generation, I don't think the extra
syntax is a problem.

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






Re: Haskell 98: getting there

1998-11-09 Thread Hans Aberg

At 03:12 -0800 1998/11/09, Simon Peyton-Jones wrote:
* Default default.  Still undecided (sigh).  Should it be
   (Int, Float)
   (Integer, Double)
   (Integer, Rational)
  Several folk want Integer, but don't say whether they want Float,Double,
  Rational.

  I think the default should be (Integer, Rational, Double) :-); none of
these types are really mathematically interchangeable. It is prudent to use
Double (64-bit IEEE floating numbers) over Float (32-bit IEEE floating
numbers) as a default, as 32-bit CPU's and better are likely to compute
Float operations by first converting them to Doubles: So Floats are then
are then slower with less precision, and the memory difference requirement
is normally not of any importance.

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







hugs and ghc compatibility and features

1998-11-09 Thread S. Alexander Jacobson

I have been reading about the integrated runtime system between GHC and
Hugs.   Now that GHC 4.0 is out, what is the status of the hugs ghc
integration project?

1. Does hugs now support mutually recursive modules?  
2. Does the new GHC support TREX? If yes, how does one enable it?
3. Are the literate modes now compatible? (they weren't before)
4. Does Hugs now support MPTC, Existential types, etc?

If so, where is this new version of hugs and how long until public
release?

-Alex-

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






RE: Haskel Type Question

1998-11-09 Thread Chris Angus

I'm guessing that the problem is that 

fos -0.5 [1,1,1,1]

is being parsed as 

((fos) - (0.5)) [1,1,1,1]

so that the 0.5 implies an instance of class Fractional which implies 
by the type of (-)

(-) :: Num a = a - a - a

that fos is also an instance of class Fractional

But since it isnt we get an error

if you do a 

fos (-0.5) [1,1,1,1]

this is parsed as 

fos (negate 0.5) [1,1,1,1] ... etc

This is the reason I prefer the notation

negate x = ~x  

and subtract x y = x - y

which means that (-x) is a section and (~x) is a negation


As I say I am not completely sure this is the 'exact' reason 
since I thought that the above example would parse as

(fos) - (0.5 [1,1,1,1])

Clearly garbage!
it will however certainly be along these lines.

Hope this helps 

Chris


 -Original Message-
 From: [EMAIL PROTECTED] 
 [mailto:[EMAIL PROTECTED]]On
 Behalf Of Matthew Donadio
 Sent: Monday, November 09, 1998 2:02 PM
 To: Haskell List
 Subject: Haskel Type Question
 
 
 I have two functions
 
  fos:: Num a - [a] - [a]
  fos a x = fos' a 0 x
 
  fos':: Num a - a - [a] - [a]
  fos' _ _  [] = []
  fos' a y1 (x:xs) = y : fos' a y xs
 where y = a * y1 + x
 
 Why does
 
  fos -0.5 [ 1, 1, 1, 1 ]
 
 give me
 
 [a] - b - [b] - [b] is not an instance of class "Fractional"
 
 while
 
  fos (-0.5) [ 1, 1, 1, 1 ]
 
 evaluates just fine?  I'm using Hugs 1.4.  Thanks.
 
 -- 
 Matt Donadio ([EMAIL PROTECTED]) | 43 Leopard Rd, Suite 102
 Sr. Software Engineer | Paoli, PA 19301-1552
 Image  Signal Processing, Inc.   | Phone: +1 610 407 4391
 http://www.isptechinc.com | FAX:   +1 610 407 4405