Showing tuples
Hi, I am having trouble with Show and tuples. I have a data structure, say: data MyData = ... And a value, say: value = (MyData..., MyData..., MyData) Then try to: show value I get a compiler message from ghc 4.05 that says: No instance for `Show (MyData, MyData, MyData)... What is the best way to deal with this problem? Thanks, Mike
Converting float to double.
I have a very simple question. What is the best way to convert a float to a double? I use fromRational.toRational, and the notes in the prelude seem to imply that this is optimized into something sensible.. is this the way? Cheers! + Ron Legere -- http://www.its.caltech.edu/~legere Caltech Quantum Optics MC 12-33 Pasadena CA 91125 626-395-8343 FAX: 626-793-9506 +
Re: basAlgPropos. Why sample argument
Sun, 7 May 2000 16:13:46 +0400 (MSD), S.D.Mechveliani <[EMAIL PROTECTED]> pisze: > Also what do you do with > class Foo a where weightOfType :: Int > ? In this case one solution is to have a sample argument, because Haskell does not provide more convenient way of parametrizing values by a type that is not a part of the type of the value. There exists an elegant solution, but it's a bit less convenient to use: newtype Const a b = Const a class Foo a where weightOfType :: Const Int a I'm not convinced whether it would be a good thing or not. Maybe it should wait for more complete support for naming lambda-bound type variables, i.e. pattern type signatures and result type signatures (GHC and Hugs have them, but introducing variables in result type signatures does not work in GHC yet). It would make it more convenient, while from the beginning it clearly describes the intent and provide everything needed for easy optimization. > What we have for the *variable dimension* n ? Haskell does have polymorphic recursion, and I hope local universal quantification will get into Haskell2. Thus variable length vectors can be expressed in a statically typed style, when the type alone determines the domain: data Vec0 a = Vec0 data Vec v a = Vec a (v a) class Vector v where listToVec :: [a] -> v a vecToList :: v a -> [a] dim :: v a -> Int -- Sample argument, may be translated to Const. zero :: HasZero a => v a instance Vector Vec0 where listToVec [] = Vec0 vecToList Vec0 = [] dim _ = 0 zero = Vec0 instance Vector v => Vector (Vec v) where listToVec (x:xs) = Vec x (listToVec xs) vecToList (Vec x xs) = x : vecToList xs dim ~(Vec x xs) = 1 + dim xs zero = Vec zero zero -- When the dimension used inside a computation disappears outside, -- i.e. when it is determined at runtime, there must be a way of -- introducing the context from the integer: instVec:: Int -> (forall v. Vector v => v a -> x) -> x instVec 0 f = f Vec0 instVec n f = instVec (n-1) (\v -> f (Vec undefined v)) -- Again Const can be used instead of the sample argument here. -- The dimension is part of the context of a computation. Not of -- individual values, as would be in typical OO languages. -- __("$ P+++ L++>$ E- ^^ W++ N+++ o? K? w(---) O? M- V? PS-- PE++ Y? PGP+ t QRCZAK 5? X- R tv-- b+>++ DI D- G+ e> h! r--%>++ y-
Re: Show class on ADT with function
George writes: > There is no problem with Showing functions with finite domains. > For example, try: > module ShowFun where > instance (Show a) => Show (Bool -> a) where >show f = show ((f True),(f False)) > instance (Show a) => (Show (Int -> a)) Why stop there? Eq and Read too, though they do become tricky at Int->Int. Ian Stark http://www.dcs.ed.ac.uk/home/stark LFCS, Division of Informatics, The University of Edinburgh, Scotland
Haskell Web Server: please pummell
Dear Haskell folks, There's a web server written in Haskell running on haskell.org: http://www.haskell.org:8080/ Please surf on over and press reload a few times. First one to bring it down gets a gold star. I'll be watching the logs :-) The source (not properly packaged, just source code, a Makefile and an example config file) is here: http://research.microsoft.com/~simonmar/hws.tar.gz You'll need a *very* up-to-date GHC (< 2 weeks old) to compile it. All we need now is: - a better name for this thing - a "powered by Haskell" logo :-) Cheers, Simon
RE: Performance, and algorithms
> * I find it difficult to understand how the code I write translates > into actual algorithms, memory management, etc. Haskell is such a > nice language that it hides all this detail from me :-). So, I'd be > grateful for a reference or two on this area. Manuel pointed out Simon's paper on the STG machine, which is a good place to start. You can see the STG code before code generation for any given module by adding the -ddump-stg option to GHC's command line (you can also see Core, GHC's typed intermediate language, by using -ddump-simpl, but that tends to include a lot of type information and can be harder to read). > * I added a reasonable amount of added strictness in `obvious' kind of > places, but with no visible effect on performance. Does adding > strictness help with CPU use as well as with memory use ? Where is it > most beneficial to add strictness ? Strictness annotations on data constructor arguments are usually a good idea. With GHC, if you mark a constructor argument strict and it's a single-constructor or flat datatype (eg. Int or a tuple), and you give the flag '-funbox-strict-fields', then the argument will be unboxed. This can be a big win, but may be a slight loss in certain conditions. We're looking for evidence to support making -funbox-strict-fields the default. > * Most of my program is in a state-threading monad of my own (built > out of normal functional pieces). The main program (which is in the > IO monad) invokes the `grind handle on state machine' function, > passing the action to perform and the initial state and getting the > new state back. Is this good, bad, or ugly ? It does make it easy to > decouple the nasty I/O handling event loop part of the program from > the clean, supposedly predictable, state engine. (Yes, the program > does really need to be a state engine.) If you don't need a lazy state monad, strict ones are usually faster. eg. m >>= k = \s -> case m s of (a, s) -> k a s is going to be faster than m >>= k = \s -> let (a, s') = m s in k a s' If you can use the ST monad instead of your own monad, that will be faster still, since the ST monad (and IO) has virtually zero overhead in GHC. > * In particular, the bit of code that seems to be slow is the part > responsible for updating a part of the state whose type is broadly > speaking > >Array (x,y) [value] > > I need to do similar cumulative updates to the values in a whole > region of the array, and I do it with (basically) this [snip] Take a look at the new IArray and MArray modules in GHC's lang library. They have some nice abstractions over flat mutable and immutable arrays, and still support some of Haskell's nice Array combinators, such as accum. You'll need to have an underlying ST or IO monad to use the mutable versions, though. Cheers, Simon
RE: Type and class names
> Why are type constructors and classes in the same namespace? Because otherwise the syntax module M ( T ) where would be ambiguous. I suppose it could be resolved to mean "export the class and/or data type T". It was proposed for Haskell 98 that the syntax be changed to module M ( class T ) where or module M ( type T ) where but the proposal was not adopted, because of the amount of breakage this would cause. Cheers, Simon
Re: sample argument. Dongen's example
S.D.Mechveliani ([EMAIL PROTECTED]) wrote: [I cc'd this to haskell as well] : this is exactly the Domain conversion proposal, described in : basAlgPropos. class Cast a b where cast :: a -> b -> a. : The first argument is the sample for domain. The second casts to : `a' after the given sample. For example cast (x^2+y (in Z[x,y)) 2 : maps 2 to polynomial in x,y : - if the instance Cast (Pol ..) Integer : is defined. I knew you must have had something to obtain a similar functionality this as well. It is needed. Regards, Marc
Cast by sample
Marc Van Dongen writes about the need of constant :: a -> b -> and explains that it is needed, for example, to convert constant to polynomial. I consider this as kind of support for the Domain conversion proposal in basAlgPropos, section 'dcon'. It suggests class Convertible which I would like to reformulate now as class Cast a b where cast :: CastMode -> a -> b -> a Example: cast _ f 2 makes a polynomial from 2 :: Integer, if instance (Pol ..) Integer is defined. f serves as the sample that denotes the particular domain of polynomials. This may be, for example - in [x] or in [x,y] - different domains. Of course, the eager usage of Cast would often cause the ambiguity - compile-time report. Still the thing is useful in practice. And mathematically, it is a highly cultural approach - to cast between the domains. It is on the user how wide and how wise to set the Cast instances - the user knows that it is often hard for Haskell to solve such instances. I tried this in practice with GHC, Hugs - a very useful thing. -- Sergey Mechveliani [EMAIL PROTECTED]
CFP: Workshop on Program Generation
[Reminder: Deadline in two weeks.] LAST CALL FOR PAPERS Semantics, Applications and Implementation of Program Generation (SAIG) ICFP Workshop, Montreal, September 20th, 2000. (Deadline: May 22, 2000) http://www.md.chalmers.se/~taha/saig/ Numerous recent studies investigate different aspects of program generation systems, including their semantics, their applications, and their implementation. Existing theories and systems address both high-level (source) language and low-level (machine) language generation. A number of programming languages now supports program generation and manipulation, with different goals, implementation techniques, and targeted at different applications. The goal of this workshop is to provide a meeting place for researchers and practitioners interested in this research area, and in program generation in general. Scope: The workshop solicits submissions related to one or more of the following topics: - Multi-level and multi-stage languages, staged computation, - Partial evaluation (of e.g. functional, logical, imperative programs), - Run-time specialization (in e.g. compilers, operating systems), - High-level program generation (applications, foundations, environments), - Symbolic computation, in-lining and macros, Submissions are especially welcome if they relate ideas and concepts from several topics, bridge the gap between theory and practice, cover new ground, or report exciting applications. The program committee will be happy to advise on the appropriateness of a particular subject. Distribution: Accepted papers will be published as a Chalmers technical report, and will be made available online. A special issue of the Journal of Higher Order and Symbolic Computation (HOSC) is planned afterwards. Format: The one-day workshop will contain slots for participants to present accepted papers. In addition, there will be time allocated for open discussions during the workshop. Invited speakers will be announced in the near future. Invited Speaker: Frank Pfenning, CMU Submission Details: Authors are invited to submit papers of at most 5000 words (excluding figures), in postscript format (letter or A4), to [EMAIL PROTECTED] by 22nd May 2000. Both position and technical papers are welcome. Please indicate at time of submission. Position papers are expected to describe ongoing work, future directions, and/or survey previous results. Technical papers are expected to contain novel results. All papers will be reviewed by the program committee for the above mentioned criteria, in addition to correctness and clarity. Authors will be notified of acceptance by 3 July 2000. Final version of the papers must be submitted by 31 July 2000. Program Committee: Cliff Click, Sun Micro Systems Rowan Davies, CMU Torben Mogensen, DIKU Suresh Jagannathan, NEC Research Tim Sheard, OGI Walid Taha, Chalmers (workshop chair) Peter Thiemann, Freiburg
[dongen@cs.ucc.ie: Re: sample argument. Dongen's example]
Sorry about this. I thought I group replied when replied Sergey's e-mail. -- Marc van Dongen, CS Dept | phone: +353 21 4903578 University College Cork, NUIC | Fax:+353 21 4903113 College Road, Cork, Ireland | Email: [EMAIL PROTECTED] - Forwarded message from Marc van Dongen <[EMAIL PROTECTED]> - Date: Mon, 8 May 2000 11:14:03 +0100 From: Marc van Dongen <[EMAIL PROTECTED]> To: "S.D.Mechveliani" <[EMAIL PROTECTED]> Subject: Re: sample argument. Dongen's example X-Mailer: Mutt 1.0.1i In-Reply-To: <[EMAIL PROTECTED]>; from [EMAIL PROTECTED] on Mon, May 08, 2000 at 01:16:09PM +0400 S.D.Mechveliani ([EMAIL PROTECTED]) wrote: : Looks like it uses the sample argument. This p contains the : parameters that describe a polynomial domain P = c[x1..xn]. : Different ways to order the monomial set, different lists of : "variables" may mean different domains inside the *same type*. : If p contains variables ["x"], p' contains ["x","y"], : then zero p and zero p' : : have to be zeroes of very different domains corresponding to : p, p' :: a. : If you rely on the features like this, this is the very sample : argument approach. : Do you mean this? No. I meant that I didn't understand the second sentence above the one where I started my reply:-) : Classic Haskell approach: : - [] : Besides several technical hindrances of mathematical nature, it : puts certain principal restriction. : It prohibits all the mathematical practice of dynamic change of : orderings, variable lists, residue domains for different base, : generally - dynamic change of computation domain given by : *parameter*. Exactly. This has been a *great* pain in the neck for me when writing operations on polynomials using standard notation which alowed for the hiding of the additional information needed to implement fast algorithms. [...] : I suggest now zero :: a -> a or constant :: a -> c -> Regards, Marc van Dongen -- Marc van Dongen, CS Dept | phone: +353 21 4903578 University College Cork, NUIC | Fax:+353 21 4903113 College Road, Cork, Ireland | Email: [EMAIL PROTECTED] - End forwarded message -
Re: sample argument. Dongen's example
S.D.Mechveliani ([EMAIL PROTECTED]) wrote: : I wrote to list, and you reply privately. Ooops. I thought I group replied. I'll forward to the list. : I think that it is good for the list to know that someone else : appreciates the need of dynamic parameters in domain ... Which is why I decided to add something to the discussion. : But I an dumb at your> or constant :: a -> c -> : : For example, zero (2,3) = (0,0) gives zero for Int x Int. : And how to use `constant' ? Say you have a constant c in some ring k and you want to lift it (I think that's the proper term) to the polynomial ring k[X] then you can if you have a polynomial, say p, in k[X] already. Just use: constant p c. Regards, Marc -- Marc van Dongen, CS Dept | phone: +353 21 4903578 University College Cork, NUIC | Fax:+353 21 4903113 College Road, Cork, Ireland | Email: [EMAIL PROTECTED]
correction to example with Alfred ...
I wrote on Fergus's example with Alfred, Betty ... type T a = T ... instance Additive (T a) where (T x)+(T y) = T (x+y) ... It should be data T a ... instance Additive a => Additive (T a) where ...
Re: basAlgPropos. Skipping class methods
Fergus Henderson <[EMAIL PROTECTED]> writes: Also one writes, for example, zero x instead of zero `asTypeOf` x. > `asTypeOf` is effectively a builtin language construct that just > happens to be implemented as a function in the standard Prelude > (because it can be). It is even mentioned explicitly in the > main part of the Haskell report (specifically in 4.3.4), not just in > the part describing the Prelude. Anyone who is truly familiar with > Haskell will know exactly what it does. And, IMHO much more important, anyone *not* familiar enough with the language will go look it up, not mistake it for something else and end up in endless confusion. -kzm -- If I haven't seen further, it is by standing in the footprints of giants
sample argument. Dongen's example
Concerning the sample argument approach, Marc van Dongen <[EMAIL PROTECTED]> writes on May 8 2000 > I am not sure if I understand this but I also used > zero :: a -> a > to create polynomials as opposed to a function > zero :: a > The application > zero p > created a zero polynomial with certain ``built-in'' > properties like a term-order it inherited from p. Looks like it uses the sample argument. This p contains the parameters that describe a polynomial domain P = c[x1..xn]. Different ways to order the monomial set, different lists of "variables" may mean different domains inside the *same type*. If p contains variables ["x"], p' contains ["x","y"], then zero p and zero p' have to be zeroes of very different domains corresponding to p, p' :: a. If you rely on the features like this, this is the very sample argument approach. Do you mean this? Classic Haskell approach: - make the above ordering and variable list to be given as the *instances* of some classes. To present an ordering or a variable list would mean to define the instance for some new type, so that the name of this type denotes actually the ordering and variable list. Besides several technical hindrances of mathematical nature, it puts certain principal restriction. It prohibits all the mathematical practice of dynamic change of orderings, variable lists, residue domains for different base, generally - dynamic change of computation domain given by *parameter*. In many tasks it is unknown statically, how many residue domains Z/(2), Z/(3) ... will suffice to find some solution. Therefore, the advancedAlgebra library should allow many domains Z/(m) with different m to exist inside the same type T. This is *partly* supported via the sample argument approach. I think, the very language cannot support this as good as the static types. And after a snob user sets a couple of times `zero p', after this, one just forgets of zero :: a, zero `asTypeOf` x. This was the story with me, personally. For 5 years I recalled the thought whether zero `asTypeOf` x is more likely to be detected as a constant than `zero p'. I argued about this, not mentioning the dynamic domains, though knew well that the readers would still fix it. I suggest now zero :: a -> a only for -fadvancedAlgebra. And note that there, the sample argument shows that the function may occur not a constant on the *type*. Instead, it is a constant on implicit domain. Domains via dynamic loading --- "I think, the very language cannot support this as good as the static types". Imagine the dynamic link of the objects modules, or generally, the dynamic loading of some interpreted code. This may do the dynamic creation of domains presented in old system like static instances. The questions are: (1) expenses, (2) does the functionality break? (1) A domain is created only to be used many times. Still ... (2) In what way f x = 1 may change to f x = 2 after loading some domain? -- Sergey Mechveliani [EMAIL PROTECTED]