Re: [Haskell-cafe] Qualified import syntax badly designed (?)

2008-07-09 Thread Thomas Davie
I think a better design for namespacing might be: import Data.Map as M implicit (Map) import Data.Map as M explicit (lookup) Why 'implicit' and 'explicit'? Do you mean something like 'include' and 'exclude'? To me at least, implicit and explicit make more sense. I don't want to exclude

Re: [Haskell-cafe] use of the GHC universal quantifier

2008-07-09 Thread Ryan Ingram
Try {-# LANGUAGE RankNTypes #-}? forall does denote a universal quantifier, but because the 'implies' of the function arrow, in logic, includes negation, you can use it to emulate existential quantifiers. data Existential = forall a. Ex a The type of the constructor Ex: Ex :: forall a. a -

Re: [Haskell-cafe] FPGA / Lava and haskell

2008-07-09 Thread Marc Weber
You're going to design something like that with an FPGA in it? :) The FPGA is only used for developement. If everything works fine I'd like to put it on the market. My hope is to get one low cost chip doing everything this way. Would you suggest using other tools? I'm still a total noob in this

Re: [Haskell-cafe] Re: Interesting feature

2008-07-09 Thread Yitzchak Gale
David Overton wrote: Also, see my recent attempts at (constraint) logic programming in Haskell: http://overtond.blogspot.com/2008/07/pre.html http://overtond.blogspot.com/2008/07/haskell-sudoku-solver-using-finite.html See the Sudoku page on the wiki: http://www.haskell.org/haskellwiki/Sudoku

Re: [Haskell-cafe] Qualified import syntax badly designed (?)

2008-07-09 Thread Neil Mitchell
Hi declaration with a regular syntax. For example: import Data.Map as Map unqualified (Map, (\\)) qualified (lookup, map, null) hiding (filter) I think I prefer this to my proposal, plus its closer to the current syntax. I think its also nearly equal to

Re: [Haskell-cafe] Qualified import syntax badly designed (?)

2008-07-09 Thread allan
Neil Mitchell wrote: Hi declaration with a regular syntax. For example: import Data.Map as Map unqualified (Map, (\\)) qualified (lookup, map, null) hiding (filter) I think I prefer this to my proposal, plus its closer to the current syntax. I think

Re: [Haskell-cafe] Qualified import syntax badly designed (?)

2008-07-09 Thread Neil Mitchell
Hi Just to say that I also like this design. A minor point would be; do we really need the parentheses and commas? or could we not just use indentation (I think this about module imports in general). Yes, then you could just uses {a;b} to get the list which is actually a newline list. I

Re: [Haskell-cafe] Qualified import syntax badly designed (?)

2008-07-09 Thread allan
Neil Mitchell wrote: Hi Just to say that I also like this design. A minor point would be; do we really need the parentheses and commas? or could we not just use indentation (I think this about module imports in general). [snip general agreement] However, I think the new syntax for

Re: [Haskell-cafe] Qualified import syntax badly designed (?)

2008-07-09 Thread Henning Thielemann
On Wed, 9 Jul 2008, Neil Mitchell wrote: For example, in the module I'm currently working on: module Hoogle.DataBase.TypeSearch.Graph( Graph, newGraph, GraphResult(..), ArgPos, Binding, graphSearch ) where I dislike the fact that ,'s come after every line but the last - it lacks

Re: [Haskell-cafe] Qualified import syntax badly designed (?)

2008-07-09 Thread Isaac Dupree
Neil Mitchell wrote: Hi declaration with a regular syntax. For example: import Data.Map as Map unqualified (Map, (\\)) qualified (lookup, map, null) hiding (filter) I think I prefer this to my proposal, plus its closer to the current syntax. I think its

Re: [Haskell-cafe] Qualified import syntax badly designed (?)

2008-07-09 Thread Stuart Cook
On Wed, Jul 9, 2008 at 10:01 AM, Neil Mitchell [EMAIL PROTECTED] wrote: It seems that the qualified import syntax is a bit awkward. At the moment, its common to see: import qualified Data.Map as M import Data.Map(Map) i.e. import a module, give it an alias (M), and put some things in the

[Haskell-cafe] QuickCheck: outdated manual

2008-07-09 Thread Roman Cheplyaka
Online QC manual[1] says[2] that 'vector' takes number of elements and generator, while in QuickCheck-1.1.0.0 it takes only number and generates vector of arbitrary's. Please fix that. By the way, I find the old version as useful as the new one. Although both are trivially implemented, I don't

Re: [Haskell-cafe] Re: Interesting feature

2008-07-09 Thread David Overton
2008/7/9 Yitzchak Gale [EMAIL PROTECTED]: David Overton wrote: Also, see my recent attempts at (constraint) logic programming in Haskell: http://overtond.blogspot.com/2008/07/pre.html http://overtond.blogspot.com/2008/07/haskell-sudoku-solver-using-finite.html See the Sudoku page on the

[Haskell-cafe] How to do a special kind of comment with the TokenParser

2008-07-09 Thread John Ky
Hi, TokenParser supports two kinds of comments, the multi-line comments (ie. {- -}) and the single line comments (ie. -- \n). The language I am trying to parse, however, has comments which are neither. The -- acts like a single line comment which extends to the end of the line usually, but can

Re: [Haskell-cafe] FPGA / Lava and haskell

2008-07-09 Thread Philip Weaver
On Wed, Jul 9, 2008 at 2:22 AM, Marc Weber [EMAIL PROTECTED] wrote: You're going to design something like that with an FPGA in it? :) The FPGA is only used for developement. If everything works fine I'd like to put it on the market. My hope is to get one low cost chip doing everything this

[Haskell-cafe] Re: How to do a special kind of comment with the TokenParser

2008-07-09 Thread Christian Maeder
TokenParser seems to pose more problems than it solves. I think it is usually easier to define your own scanner and avoid the necessary Haskell language extensions used there. (Surely parts of the code from TokenParser can be copied.) Cheers Christian John Ky wrote: Hi, TokenParser supports

[Haskell-cafe] CAL (OpenQuark) and enterprise

2008-07-09 Thread fero
Hi Haskellers and CALers, I have the feeling that a lot of code in my jee application can be done better by using functional programming. There is a lot of searching in object trees, transforming objects to another objects, aggregation functions... All written in java. Sequential logic can by

Re: [Haskell-cafe] Qualified import syntax badly designed (?)

2008-07-09 Thread Jonathan Cast
On Wed, 2008-07-09 at 12:36 +0200, Henning Thielemann wrote: On Wed, 9 Jul 2008, Neil Mitchell wrote: For example, in the module I'm currently working on: module Hoogle.DataBase.TypeSearch.Graph( Graph, newGraph, GraphResult(..), ArgPos, Binding, graphSearch ) where

Re: [Haskell-cafe] CAL (OpenQuark) and enterprise

2008-07-09 Thread Neil Mitchell
Hi There is a lot of searching in object trees, transforming objects to another objects, aggregation functions... Sounds like you want: Either Uniplate: http://www-users.cs.york.ac.uk/~ndm/uniplate/ Or SYB: http://www.cs.vu.nl/boilerplate/ Read through both papers for various examples of

Re: [Haskell-cafe] FPGA / Lava and haskell

2008-07-09 Thread Don Stewart
marco-oweber: Is Haskell still used (in industry as well ?) to write (V)HDL code to program FPGAs and create circuits on chips? The Chalmers Lava homepage tells abouta Xilinx version which should be merged in soon. But on the xilinx homepage there was no reference to neither Lava nor

Re: [Haskell-cafe] Qualified import syntax badly designed (?)

2008-07-09 Thread David Menendez
On Wed, Jul 9, 2008 at 1:03 AM, wren ng thornton [EMAIL PROTECTED] wrote: What I would like to see is the ability to do (1) module renaming, (2) qualified import, (3) unqualified import, and (4) hiding all in a single declaration with a regular syntax. For example: import Data.Map as Map

[Haskell-cafe] Haskell Weekly News: Issue 76 - July 9, 2008

2008-07-09 Thread Brent Yorgey
--- Haskell Weekly News http://sequence.complete.org/hwn/20080709 Issue 76 - July 09, 2008 --- Welcome to issue 76 of HWN, a newsletter covering

Re: [Haskell-cafe] Qualified import syntax badly designed (?)

2008-07-09 Thread Jason Dusek
David Menendez [EMAIL PROTECTED] wrote: I've often thought it would be for Haskell to steal Agda's module syntax. It does pretty much everything you want (plus some other stuff we maybe don't need) and the various things it does fit together logically. What does that look like? I've been

Re: [Haskell-cafe] CAL (OpenQuark) and enterprise

2008-07-09 Thread Miles Sabin
On Wed, Jul 9, 2008 at 6:28 PM, Neil Mitchell [EMAIL PROTECTED] wrote: On the Haskell list I think its fair to say everyone recommends you should use Haskell. Not necessarily. If the OP has a significant body of existing Java code (s)he has to work with (which is what the question suggests)

Re: [Haskell-cafe] Qualified import syntax badly designed (?)

2008-07-09 Thread David Menendez
On Wed, Jul 9, 2008 at 2:51 PM, Jason Dusek [EMAIL PROTECTED] wrote: David Menendez [EMAIL PROTECTED] wrote: I've often thought it would be for Haskell to steal Agda's module syntax. It does pretty much everything you want (plus some other stuff we maybe don't need) and the various things it

re: [Haskell-cafe] Swapping Monads

2008-07-09 Thread Greg Meredith
Dominic, You can also reference Eugenia Cheng's paper on arXivhttp://arxiv.org/abs/0710.1120 . Best wishes, --greg -- L.G. Meredith Managing Partner Biosimilarity LLC 806 55th St NE Seattle, WA 98105 +1 206.650.3740 http://biosimilarity.blogspot.com

Re: [Haskell-cafe] Qualified import syntax badly designed (?)

2008-07-09 Thread Jason Dusek
David Menendez [EMAIL PROTECTED] wrote: Jason Dusek [EMAIL PROTECTED] wrote: David Menendez [EMAIL PROTECTED] wrote: I've often thought it would be for Haskell to steal Agda's module syntax. What does that look like? I've been looking for some kind of documentation for ~20 minutes

[Haskell-cafe] Combining Wouter's expressions with extensible records

2008-07-09 Thread Ron Alford
Well, my extension of Wouter's datatypes proved to be unweildy So, I'm trying to use http://fmapfixreturn.wordpress.com/2008/05/03/simple-extensible-records-now-quick-generic-tricks-pt-1/ for extensible records. I ran across my first problem rather quickly! data Expr f = In (f (Expr f)) Ok,

Re: [Haskell-cafe] Combining Wouter's expressions with extensible records

2008-07-09 Thread Antoine Latter
On Wed, Jul 9, 2008 at 9:40 PM, Ron Alford [EMAIL PROTECTED] wrote: Ok, but to make it part of a record, it needs to implement Data: data Expr f = In (f (Expr f)) deriving Data but this gives No instances for (Data (f (Expr f)), Typeable (Expr f)) arising from the 'deriving' clause

[Haskell-cafe] Lazy IO

2008-07-09 Thread Ronald Guida
Suppose I have a lazy function f :: [Int] - [Int], and I happen to know that for all n, the n-th element of the output may only depend on the first (n-1) elements of the input. I want to print a number from f's output list, and then ask the user for the next number in f's input list, and then

[Haskell-cafe] Profiling nested case

2008-07-09 Thread Mitar
Hi! I am making a simple raycasting engine and have a function which take a point in space and return a color of an object (if there is any) at this point in space. And because the whole thing is really slow (or was really slow) on simple examples I decided to profile it. It takes around 60

Re: [Haskell-cafe] Lazy IO

2008-07-09 Thread Ryan Ingram
On 7/9/08, Ronald Guida [EMAIL PROTECTED] wrote: Question: If I can't change my function f (in this case, accumulator), then is it possible to get the effect I want without having to resort to unsafeInterleaveIO? Yes, but you won't like it. Since you know that (f xs !! n) only depends on the