[GHC] #698: allocaBytes does not actually free the memory after the computation

2006-02-15 Thread GHC
#698: allocaBytes does not actually free the memory after the computation
---+
Reporter:  guest   |Owner: 
Type:  bug |   Status:  new
Priority:  normal  |Milestone: 
   Component:  Compiler (FFI)  |  Version:  6.4.1  
Severity:  normal  | Keywords: 
  Os:  Linux   |   Difficulty:  Unknown
Architecture:  x86 |  
---+
allocaBytes does not appear to free the memory after the computation has
 completed. For example, start ghci and run:

 {{{allocaBytes (100*1024*1024) $ \_ - getLine}}}

 ghci's virtual memory usage will jump up by 100MB. When you press enter
 however, it does not drop back down.

 restart ghci and try:

 {{{bracket (mallocBytes 100*1024*1024) free $ \_ - getLine}}}

 This time when you press enter, the memory usage will drop back down to
 its pre mallocBytes usage.

 This also happens for compiled programs.

 Note: the above test will only alloc virtual memory since nothing is ever
 read into the malloc'd memory. The following test program will actually
 force the pages to be mapped. It results in the same broken behaviour with
 the addition that the resident size of ghci gets stuck high.
 {{{
 module Main where

 import Control.Exception
 import Foreign.Marshal.Alloc
 import Foreign.Ptr
 import Data.Word
 import System.IO
 import System.Mem

 test :: Int - IO ()
 test mb =
 let size = mb * 1024 * 1024 in
 do -- bracket (mallocBytes size) free $ wait size -- this version
 works
allocaBytes size $ wait size  -- this version does not free the
 memory afterwards
performGC

 wait :: Int - Ptr Word8 - IO ()
 wait size p =
 bracket (openBinaryFile /dev/scsi/host0/bus0/target0/lun0/part1
 ReadMode) (hClose) (\h - hGetBuf h p size  putStrLn waiting... 
 getLine  return ())

 main =
 do test 150
putStrLn is it free?
getLine
return ()
 }}}

-- 
Ticket URL: http://hackage.haskell.org/trac/ghc/ticket/698
GHC http://www.haskell.org/ghc/
The Glasgow Haskell Compiler___
Glasgow-haskell-bugs mailing list
Glasgow-haskell-bugs@haskell.org
http://www.haskell.org/mailman/listinfo/glasgow-haskell-bugs


Re: [Haskell] compares :: Ord a = a - a - Ordering - Ordering

2006-02-15 Thread Ross Paterson
On Wed, Feb 15, 2006 at 01:17:43AM +, Ben Rudiak-Gould wrote:
 I just realized that the class Ord should have an additional method:
 
   class Eq a = Ord a where
 compares :: a - a - Ordering - Ordering
 compares x y d = case compare x y of { EQ - d ; o - o }
 ...
 
 This would make writing Ord instances much easier:
 
   instance (Ord a, Ord b, Ord c, Ord d) = Ord (a,b,c,d) where
 compares (a1,b1,c1,d1) (a2,b2,c2,d2) =
   compares a1 a2 . compares b1 b2 . compares c1 c2 . compares d1 d2

This does the same thing:

import Data.Monoid

instance (Ord a, Ord b, Ord c, Ord d) = Ord (a,b,c,d) where
compare (a1,b1,c1,d1) (a2,b2,c2,d2) =
compare a1 a2 `mappend` compare b1 b2 `mappend`
compare c1 c2 `mappend` compare d1 d2

___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] Datatype-generic programming 2006, registration now open

2006-02-15 Thread Fermin Reig
[Apologies for multiple copies]


==

Registration for DGP 2006 is now open. Please visit the web site for
instructions.


Spring School on Datatype-Generic Programming 
http://www.cs.nott.ac.uk/ssdgp2006/
University of Nottingham, UK
 24-27 April 2006


 Background and objectives  

Generic programming is a thriving research area aimed at making
programming more effective by making it more general. This school aims
to give participants insights into the applications of
datatype-generic programming and the current research challenges in
the area. 

This school is a successor to the Summer School and Workshop on
Generic Programming, held in Oxford in August 2002 (lecture notes
appeared as volume 2793 of LNCS). 


 Technical programme   

The lectures will be tutorial-style (as opposed to conference-style)
and will be accessible to beginning computing science postgraduates.

The scientific programme consists of six courses given by renowned
specialists, and a student session. The list of courses is the
following:

* Thorsten Altenkirch (University of Nottingham):
  (in collaboration with Conor McBride and Peter Morris)
  Generic programming with dependent types

* Jeremy Gibbons (University of Oxford):
  Design Patterns as Higher-Order Datatype-Generic Programs
  
* Ralf Hinze (Universitat of Bonn):
  Generic Programming, Now!  
  (in collaboration with Andres Loeh)
  
* Johan Jeuring (Universiteit Utrecht):
  Comparing Approaches to Generic Programming 
  (in collaboration with Ralf Hinze and Andres Loeh)
  
* Ralf Laemmel (Microsoft)
  The next 700 traversal approaches

* Tim Sheard (Portland State University):
  Putting the Curry-Howard Isomorphism to work.

Copies of the draft lecture notes will be provided to all
participants.

The purpose of the student session is to give students an opportunity
to present their work and get feedback. Registrants are invited to
propose short talks (15-20 min). The selection will be based on
abstracts of 150-400 words.

 Social programme  

A conference dinner will be organised (attendance at which will be 
charged separately).

 Co-location  

The Symposium on Trends in Functional Programming (TFP 2006), and the
Conference of the Types Project (TYPES 2006) will be held in
Nottingham the week before this spring school.

 Accommodation  

Information about accommodation is available at the School's web site.

 APPSEM  

This is an APPSEM-affiliated event. APPSEM funds can be used to
support participants from APPSEM-affiliated sites.




This message has been checked for viruses but the contents of an attachment
may still contain software viruses, which could damage your computer system:
you are advised to perform your own checks. Email communications with the
University of Nottingham may be monitored as permitted by UK legislation.

___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] Re: compares :: Ord a = a - a - Ordering - Ordering

2006-02-15 Thread Christian Maeder

Ben Rudiak-Gould wrote:

I just realized that the class Ord should have an additional method:

  class Eq a = Ord a where
compares :: a - a - Ordering - Ordering
compares x y d = case compare x y of { EQ - d ; o - o }
...


How about:

instance (Ord a, Ord b, Ord c, Ord d) = Ord (a,b,c,d) where
compare (a1,b1,c1,d1) (a2,b2,c2,d2) =
compare ((a1,b1,c1),d1) ((a2,b2,c2),d2)

or another tuple nesting)

Christian
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Re: compares :: Ord a = a - a - Ordering - Ordering

2006-02-15 Thread Chris Kuklewicz
Christian Maeder wrote:
 Ben Rudiak-Gould wrote:
 I just realized that the class Ord should have an additional method:

   class Eq a = Ord a where
 compares :: a - a - Ordering - Ordering
 compares x y d = case compare x y of { EQ - d ; o - o }
 ...
 
 How about:
 
 instance (Ord a, Ord b, Ord c, Ord d) = Ord (a,b,c,d) where
 compare (a1,b1,c1,d1) (a2,b2,c2,d2) =
 compare ((a1,b1,c1),d1) ((a2,b2,c2),d2)
 
 or another tuple nesting)
 
 Christian

That works, but...

Constructing the new tuples is usually more heap allocation, and these short
lived data items can make the garbage collection load higher.

The `mappend` method avoids this pitfall.
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] Haskell Workshop 2006 Call for papers

2006-02-15 Thread Andres Loeh
Apologies for multiple copies; feel free to distribute further.

Cheers,
  Andres

 ACM SIGPLAN 2006 Haskell Workshop
  Call for Papers

  Portland, Oregon
 17 September, 2006


   The Haskell Workshop 2006 will be part of the 2006 International
   Conference on Functional Programming (ICFP) as an associated, ACM
   SIGPLAN sponsored workshop. Previous Haskell Workshops have been held
   in La Jolla (1995), Amsterdam (1997), Paris (1999), Montreal (2000),
   Firenze (2001), Pittsburgh (2002), Uppsala (2003), Snowbird (2004),
   and Tallinn (2005).

Topics

   The purpose of the Haskell Workshop is to discuss experience with
   Haskell, and possible future developments for the language. The scope
   of the workshop includes all aspects of the design, semantics, theory,
   application, implementation, and teaching of Haskell. Topics of
   interest include, but are not limited to, the following:
 * Language Design, with a focus on possible extensions and
   modifications of Haskell as well as critical discussions of the
   status quo;
 * Theory, in the form of a formal treatment of the semantics of the
   present language or future extensions, type systems, and
   foundations for program analysis and transformation;
 * Implementations, including program analysis and transformation,
   static and dynamic compilation for sequential, parallel, and
   distributed architectures, memory management as well as foreign
   function and component interfaces;
 * Tools, in the form of profilers, tracers, debuggers,
   pre-processors, and so forth;
 * Applications, Practice, and Experience with Haskell for scientific
   and symbolic computing, database, multimedia and Web applications,
   and so forth as well as general experience with Haskell in
   education and industry;
 * Functional Pearls being elegant, instructive examples of using
   Haskell.

   Papers in the latter two categories need not necessarily report
   original research results; they may instead, for example, report
   practical experience that will be useful to others, re-usable
   programming idioms, or elegant new ways of approaching a problem. The
   key criterion for such a paper is that it makes a contribution from
   which other practitioners can benefit. It is not enough simply to
   describe a program!

Submission details

   Submission deadline: 2 June 2006
   Notification:3 July 2006

   Submitted papers should be in postscript or portable document format,
   formatted using the ACM SIGPLAN style guidelines. The length
   should be restricted to 12 pages.

   Detailed submission instructions will be available at
   http://haskell.org/haskell-workshop/2006.

   Accepted papers will be published by the ACM and will appear in the
   ACM Digital Library.

   If there is sufficient demand, we will try to organise a time slot for
   system or tool demonstrations. If you are interested in demonstrating
   a Haskell related tool or application, please send a brief demo
   proposal to Andres Loeh ([EMAIL PROTECTED]).

Programme Committee

   Koen Claessen, Chalmers University, Sweden
   Bastiaan Heeren, Universiteit Utrecht, The Netherlands
   Paul Hudak, Yale University, US
   Isaac Jones, Galois Connections, US
   Gabriele Keller, University of New South Wales, Australia
   Oleg Kiselyov, FNMOC, US
   Andres Loeh (chair), Universitaet Bonn, Germany
   Conor McBride, University of Nottingham, UK
   Shin-Cheng Mu, Academia Sinica, Taiwan
   Andrew Tolmach, Portland State University, US

___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


[Haskell] Question for the haskell implementors: Arrays, unsafePerformIO, runST

2006-02-15 Thread John Meacham
So, I finally decided that jhc needs real arrays, but am running into an
issue and was wondering how other compilers solve it, or if there is a
general accepted way to do so.

here is what I have so far

 -- The opaque internal array type
 data Array__ a

 -- the array transformer quasi-monad
 newtype AT a = AT (Array__ - Array__)

 seqAT__ :: AT a - AT a - AT a
 seqAT__ (AT a1) (AT a2) = AT $ \a - a2 (a1 a)

 doneAT__ :: AT a
 doneAT__ = AT id

 newAT__ :: Int - AT a - Array__ a
 newAT__ n (AT a1) = a1 (prim_newAT__ n)

 writeAT__ :: Int - a - AT a
 writeAT__ i x = AT $ \a - prim_writeAT__ i x a

 -- none of these routines have run-time checks
 foreign import primitive prim_newAT__ :: Int - Array__
 -- performs *update-in-place*
 foreign import primitive prim_writeAT__ :: Int - a - Array__ - Array__
 foreign import primitive unsafeAt__ :: Array__ a - Int - a

 -- example use
 newArray :: [a] - Array__ a
 newArray xs = newAT__ (length as) $ foldr assign doneAT (zip [0..] xs) where
 assign (i,v) rs = writeAT__ i v `seqAT__` rs


now, the problem occurs in newAT__

 newAT__ :: Int - AT a - Array__ a
 newAT__ n (AT a1) = a1 (prim_newAT__ n)
^ this gets floated out as a CAF.

it all seems good, but the call to (prim_newAT__ n) is a constant and
hence gets pulled to the top level and all arrays end up being the same
array! this is no good. I always knew in the back of my mind that
'unsafePerformIO' had the same problem, but sort of punted solving it
since unsafePerformIO is not really used in any critical paths. However,
it pretty much fundamentally breaks arrays!

I imagine the same issue would arise with runST.

so, any idea how to solve it? I could brute force it and make the
compiler recognize calles to prim_newAT__ as special, but I really don't
like that idea. it is hard to guarentee such things across all possible
optimizations and I'd like a general solution rather than hardcoding a
bunch of routines as special.




So far, my best idea though I don't know if it will work is adding a
primitive:

 foreign import primitive prim_newWorld__ :: forall a . a - World__

which will throw away its argument and produce a World__. but since it
is primtive, the compiler will assume the world it returns might depend
on its argument. then I could do something like:

 foreign import primitive prim_newAT__ :: World__ - Int - Array__

 newAT__ :: Int - AT a - Array__ a
 newAT__ n (AT a1) = a1 (prim_newAT__ (prim_newWorld__ a1) n)

so the initial call to newAT__ now depends on the array transformer and
can't be floated out as a CAF.

I have reduced several magic primitives to just one, the world creation
one. but I am still not sure how happy I am about it and wanted to know
what other compilers did.


John


--
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell] Question for the haskell implementors: Arrays, unsafePerformIO, runST

2006-02-15 Thread Taral
On 2/15/06, John Meacham [EMAIL PROTECTED] wrote:
  foreign import primitive prim_newWorld__ :: forall a . a - World__

 which will throw away its argument and produce a World__. but since it
 is primtive, the compiler will assume the world it returns might depend
 on its argument. then I could do something like:

GHC uses ST, which uses RealWorld#...

--
Taral [EMAIL PROTECTED]
Computer science is no more about computers than astronomy is about
telescopes.
-- Edsger Dijkstra
___
Haskell mailing list
Haskell@haskell.org
http://www.haskell.org/mailman/listinfo/haskell


Re: [Haskell-cafe] Haskell XSLT interpreter?

2006-02-15 Thread Johan Jeuring
Has anyone written a pure haskell xslt interpreter?  If not, how  
difficult would it be to do so?


A master student of mine implemented XSLT in Haskell a couple of  
years ago.


I've uploaded his thesis on

http://www.cs.uu.nl/~johanj/MSc/danny.pdf

If you're interested in the code, mail me. His implementation is  
partially in Haskell, partially in attribute grammar code (which  
generates Haskell using the Utrecht AG system). The code hasn't been  
used since 2001, so it might contain some bitrot.


-- Johan
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Layout processing

2006-02-15 Thread Maurício

  Hi,

  Is it possible to ask GHC or other Haskell compiler to generate a 
Haskell source file just after the processing of layout? I.e., I would 
like to see this:


main = do
a - some_function

  Transformed into this:

main = do {a - some_function;

  I thought that would be usefull to understand better how layout works.

  Thanks,
  Maurício

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskell as scripting language?

2006-02-15 Thread Marc Weber
Is there a way to use haskell as scripting language in
a) your own project?
b) other projects such as vim (beeing written in C)?

At the moment I'm interested, I don't have any real project..
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: strict Haskell dialect

2006-02-15 Thread Johan Bockgård
John Meacham [EMAIL PROTECTED] writes:

 there are actually several ways to implement IO. There is a paper
 about it somewhere that explores various methods, but I can't seem
 to find it, does anyone know which one i am thinking of? I know it
 at least explores the state and continuation versions as well as
 some that don't use monads I thought. It was either part of a
 general paper on monads or something specific to doing IO...

This one?

http://research.microsoft.com/~simonpj/Papers/imperative.ps.Z

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell as scripting language?

2006-02-15 Thread Jared Updike
For scenario (a) you can use hs-plugins and ghc
  http://www.cse.unsw.edu.au/~dons/hs-plugins/
With hs-plugins you can get an eval command, or you can dynamically
load Haskell modules (from source or pre-compiled .o files).

GHC (= 6.5) has an API that you can access from Haskell programs:
  http://www.haskell.org/haskellwiki/GHC/As_a_library
I was wondering if the new GHC API gives you everything hs-plugins
does? If not will it ultimately do what hs-plugins does and replace
it, in the future?

  Jared.

On 2/15/06, Marc Weber [EMAIL PROTECTED] wrote:
 Is there a way to use haskell as scripting language in
 a) your own project?
 b) other projects such as vim (beeing written in C)?

 At the moment I'm interested, I don't have any real project..
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe



--
http://www.updike.org/~jared/
reverse )-:
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Hashtable woes

2006-02-15 Thread John Meacham
On Wed, Feb 15, 2006 at 09:42:10AM +0100, Ketil Malde wrote:
 
 Not sure how relevant this is, but I see there is a recently released
 hash library here that might be a candidate for FFIing?
 
 https://sourceforge.net/projects/goog-sparsehash/
 
 | An extremely memory-efficient hash_map implementation. 2 bits/entry
 | overhead! The SparseHash library contains several hash-map
 | implementations, including implementations that optimize for space
 | or speed.

If we want really fast maps, we should be using this. it beats the
competition by far:

 http://judy.sourceforge.net/

John

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Hashtable woes

2006-02-15 Thread Jan-Willem Maessen


On Feb 15, 2006, at 3:42 AM, Ketil Malde wrote:



Not sure how relevant this is, but I see there is a recently released
hash library here that might be a candidate for FFIing?

https://sourceforge.net/projects/goog-sparsehash/


The real issue isn't the algorithms involved; I saw the best  
performance from the stupidest hash algorithm (well, and switching to  
multiplicative hashing rather than mod-k).  The problem is GC of hash  
table elements.  FFI-ing this library would give us really good  
algorithms, but the GC would all indirect through the FFI and I'd  
expect that to make things *worse*, not better.


-Jan



| An extremely memory-efficient hash_map implementation. 2 bits/entry
| overhead! The SparseHash library contains several hash-map
| implementations, including implementations that optimize for space
| or speed.

-k
--
If I haven't seen further, it is by standing in the footprints of  
giants


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: strict Haskell dialect

2006-02-15 Thread John Meacham
On Wed, Feb 15, 2006 at 04:58:34PM +0100, Johan Bockgård wrote:
 John Meacham [EMAIL PROTECTED] writes:
 
  there are actually several ways to implement IO. There is a paper
  about it somewhere that explores various methods, but I can't seem
  to find it, does anyone know which one i am thinking of? I know it
  at least explores the state and continuation versions as well as
  some that don't use monads I thought. It was either part of a
  general paper on monads or something specific to doing IO...
 
 This one?
 
 http://research.microsoft.com/~simonpj/Papers/imperative.ps.Z
 

Ah, yes. perhaps we could get a local copy of every paper somewhere on
haskell.org so we can do a scholar.google.com search with
site:haskell.org to get full text search of all relevant haskell
papers.

John 

-- 
John Meacham - ⑆repetae.net⑆john⑈
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Haskell as scripting language?

2006-02-15 Thread Donald Bruce Stewart
jupdike:
 For scenario (a) you can use hs-plugins and ghc
   http://www.cse.unsw.edu.au/~dons/hs-plugins/
 With hs-plugins you can get an eval command, or you can dynamically
 load Haskell modules (from source or pre-compiled .o files).
 
 GHC (= 6.5) has an API that you can access from Haskell programs:
   http://www.haskell.org/haskellwiki/GHC/As_a_library
 I was wondering if the new GHC API gives you everything hs-plugins
 does? If not will it ultimately do what hs-plugins does and replace
 it, in the future?

It doesn't have the high level api. Sean Seefried actually implemented
an hs-plugins-like interface to some bits of GHC, and I'd expect that 
hs-plugins 2 will just be a layer over ghc-api (or maybe part of
ghc-api).

Certainly the object loading and (ghci-based) evaluation could be moved
from hs-plugins to ghc-api. The file merging operations, and possibly
the native-code evaluation would require adding a layer over ghc-api.

-- Don
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Haskell' Status

2006-02-15 Thread Isaac Jones
I'll try to occasionally post an announcement of the the status of
Haskell'[1], the next Haskell standard, so that you can all be aware of
my thinking, and our current place in the timeline.

There is a list of proposals and a strawman categorization of them
on the wiki[2].  The categorization reflects someone's current
thinking about what's in and out, but it's really just for discussion
at this phase.

The timeline for this effort is also on the wiki[4].  You'll notice
that it's very aggressive; we plan to announce something at the next
Haskell Workshop in September.

Our current spot in the timeline is that we're meant to be
brainstorming, discussing, and refining proposals.  I've just posted
some leading questions [3] in order to focus the discussion a bit.

I can't help but notice that there is a lot of excitement (and
support?)  for a larger standard; one that would have a bigger impact.
I think that part of the Haskell' effort should be to make a plan for
moving forward.  At the very least we should have a set of
recommendations for what the community needs to work on between this
and the next standard; what are the most promising proposals and what
needs to happen to make them a reality.  I think that the wiki will be
a great resource for any future standard, and we should work to make
it as nice as possible.

Please reply to the Haskell' mailing list, and email me if you have
any questions.

peace,

  isaac


[1] Haskell' Wiki: http://hackage.haskell.org/trac/haskell-prime

[2] list of proposals and strawman categorization:
http://hackage.haskell.org/trac/haskell-prime/report/9

[3] plan for moving discussion forward
http://www.haskell.org//pipermail/haskell-prime/2006-February/000582.html

[4] The TimeLine is here.  Ascii text of the timeline follows (might
not make sense unless you use a proportional font:
http://hackage.haskell.org/trac/haskell-prime/wiki/TimeLine

 Write ReportReview
 |  | Edit|
   Discuss / Refine--|--| |
   | | || |
   brainstorm--- | || |
   |   |   | | || |
setup  |   | | || |
 | |   | | || |
---
10 | 11 | 12 | 01 | 02 | 03 | 04 | 05 | 06 | 07 | 08 | 09 | 10 | 11
2005   2006
---
 |   |  |   |
 |   |  Face-To-Face?   |
 StrawmanTrial Decision Announce
@HW
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Code completion? (IDE)?

2006-02-15 Thread Marc Weber
vim7 has introduced omni-completion... So I'm interested wether there
are any projects which support any kind of completion.?

I've read the thread about Eclipse IDE haskell plugin.

Would you recommend picking up code from a haskell compiler and adapt
it for this purpose?

I'm interested but don't plan to implement this in the near
future.

Marc
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Re: Associated Type Synonyms question

2006-02-15 Thread Stefan Wehr
Niklas Broberg [EMAIL PROTECTED] wrote::

 On 2/10/06, Ross Paterson [EMAIL PROTECTED] wrote:
 On Fri, Feb 10, 2006 at 05:20:47PM +0100, Niklas Broberg wrote:
  - when looking at the definition of MonadWriter the Monoid constraint
  is not strictly necessary, and none of the other mtl monads have
  anything similar. Is it the assumption that this kind of constraint is
  never really necessary, and thus no support for it is needed for ATS?

 I think that's right -- it's only needed for the Monad instance for
 WriterT.  But it is a convenience.  In any instance of MonadWriter, the
 w will be a monoid, as there'll be a WriterT in the stack somewhere,
 so the Monoid constraint just saves people writing general functions
 with MonadWriter from having to add it.

 Sure it's a convenience, and thinking about it some more it would seem
 like that is always the case - it is never crucial to constrain a
 parameter. But then again, the same applies to the Monad m constraint,
 we could give the same argument there (all actual instances will be
 monads, hence...). So my other question still stands, why not allow
 constraints on associated types as well, as a convenience?

Manuel (Chakravarty) and I agree that it should be possible to
constrain associated type synonyms in the context of class
definitions. Your example shows that this feature is actually
needed. I will integrate it into phrac within the next few days.

Stefa

___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe