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 importing lookup, I want to make it so I have to explicitly  
tag lookup as being M.lookup.  Similarly, I don't want to include Map  
(as opposed to all the other things I'm getting from Data.Map), I just  
want to make it so that when I say Map, I implicitly mean M.Map.


Personally I'd extend this syntax (something Neil may have had in  
mind), so that


import Data.Map as M (lookup, union) implicit (Map)
gives me M.lookup, M.union and Map

while
import Data.Map as M hiding (union) explicit (lookup)
gives me everything in Data.Map with no qualification except for union  
and lookup, plus it gives me M.lookup.


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


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 - Existential

Pattern matching on Ex brings a back into scope (with no information
about it, so this type isn't that useful on its own):

 use (Ex x) = 0 -- can't recover any useful information about x
 sample = Ex sample

However, you can use existential types to encode additional
information about the included data; for example:

 -- Ex2 :: forall a. Show a = a - Exist2
 data Exist2 = forall a. Show a = Ex2 a

Now, pattern matching on Ex2 brings the Show instance into scope as well:

 sample2 = Ex2 sample2
 use2 (Ex2 x) = show x

You can also use higher rank polymorphism to encode existential types:

 -- Ex3 :: (forall a. (forall b. Show b = b - a) - a) - Exist3
 -- note the rank-3 type on Ex3!
 newtype Exist3 = Ex3 (forall a. (forall b. Show b = b - a) - a)

 sample3 = Ex3 (\k - k sample3)
 use3 (Ex3 f) = f (\x - show x)

  -- ryan

2008/7/8 Galchin, Vasili [EMAIL PROTECTED]:
 Hello,

  It seems to me by its name that forall denotes a logical universal
 quantifier. In any case, hsql-1.7/Database/HSQL/Types.hs uses forall at
 line #134. I got a nasty build so I added {-# LANGUAGE
 ExistentialQuantification #-} at the top of the module. Now I get the
 following a coupleof lines up:

 Database/HSQL/Types.hs:131:5:
 Illegal polymorphic or qualified type: forall a.
Int
- FieldDef
- FieldDef
- CString
- Int
- IO a
- IO a
 In the definition of data constructor `Statement'
 In the data type declaration for `Statement'

 If seems that GHC doesn't like a. Why?

 Kind regards, Vasili

 ___
 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] 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 area

 For a simple enough design, it can be useful to write specs in Haskell and
 then translate them to HDL by hand.  I believe someone on this list had a
 particularly successful experience doing that :).

Thanks for this note.

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


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

Please add your solver there.

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


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 what Tom Davie came up with,
given some keyword renaming. If we dropped the unqualified keyword,
and just required unqualified things to come directly after, we get
the full benefits of not introducing any keywords.

  * A special case can be made when all three clauses are dropped so that, if
 there's no 'as'-clause then everything is imported unqualified, otherwise
 everything is imported qualified.

That's not the current semantics. Currently 'as' means everything is
imported unqualified and also qualified.

 Why 'implicit' and 'explicit'? Do you mean something like 'include' and 
 'exclude'?

I want to refer to these things explicitly (with a module name), I
want to refer to these things implicitly (without a module name). I
have no particular attachment to the keywords - think of it as a
discussion starter rather than a suggestion.

Thanks

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


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 its also nearly equal to what Tom Davie came up with,
 given some keyword renaming. If we dropped the unqualified keyword,
 and just required unqualified things to come directly after, we get
 the full benefits of not introducing any keywords.
 
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).

Also I wouldn't mind 'as' for the names which are imported which would
be a bit of a work around for the debate as to whether I should design
my modules for qualified import or not. Suppose I make a 'NewList'
module and use the default names then someone could do:
import Data.NewList
  unqualified map  as nlMap
  find as nlFind
  lookup as nlLookup

or vice-versa.

regards
allan

-- 
The University of Edinburgh is a charitable body, registered in
Scotland, with registration number SC005336.

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


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 think this would be even better for module
declarations.

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 consistency, and often requires 1 more line of diff when adding
somethign (add comma to previous line, and add the line). I would
rather write:

module Hoogle.DataBase.TypeSearch.Graph{
Graph; newGraph
GraphResult(..); ArgPos; Binding
graphSearch
} where

However, I think the new syntax for modules, and the new type of
declarations for modules, are separate issues.

  Also I wouldn't mind 'as' for the names which are imported which would
  be a bit of a work around for the debate as to whether I should design
  my modules for qualified import or not. Suppose I make a 'NewList'
  module and use the default names then someone could do:
  import Data.NewList
   unqualified map  as nlMap
   find as nlFind
   lookup as nlLookup

I believe old versions of Haskell had this, and it was considered too
confusing. Consider:

import Prelude unqualified (+) as (-)

Also people reading the code will find it easier to know N =
Data.NewList (one mapping), than three mappings as you have.

Thanks

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


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 modules, and the new type of
 declarations for modules, are separate issues.

Sure!

 
  Also I wouldn't mind 'as' for the names which are imported which would
  be a bit of a work around for the debate as to whether I should design
  my modules for qualified import or not. Suppose I make a 'NewList'
  module and use the default names then someone could do:
  import Data.NewList
   unqualified map  as nlMap
   find as nlFind
   lookup as nlLookup
 
 I believe old versions of Haskell had this, and it was considered too
 confusing. Consider:
 
 import Prelude unqualified (+) as (-)
 
 Also people reading the code will find it easier to know N =
 Data.NewList (one mapping), than three mappings as you have.
 

Yes I generally agree there, I don't think 'as' for imported names is
particularly important and if it's been tried before and found to be
confusing well then that pretty much settles it for me.
If I were particularly for it then I'd point out that:
import Prelude unqualified (+) as (-)
would only be written by someone with limited common sense or someone
trying to break things (but I'm sure you could come up with a more
realistic example).
More importantly for me is the consistency you mentioned, for me it
seems inconsistent that you can remap a module name but not an imported
identifier. That said, your point about knowing one or three mappings is
somewhat compelling and I'm now somewhat less in favour of 'as' for
imported names.

regards
allan

-- 
The University of Edinburgh is a charitable body, registered in
Scotland, with registration number SC005336.

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


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 consistency, and often requires 1 more line of diff when adding
somethign (add comma to previous line, and add the line). I would
rather write:


Also in the current syntax it is allowed to add a comma in the last line.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 also nearly equal to what Tom Davie came up with,
given some keyword renaming. If we dropped the unqualified keyword,
and just required unqualified things to come directly after, we get
the full benefits of not introducing any keywords.


We're still not introducing any keywords either way, fortunately :-). 
'qualified', 'as' and 'hiding' are not keywords: the syntax after 
'import' has no place for lowercase identifiers, so we can use as many 
new words as we want, here, as long as module names stay capitalized and 
import lists remain parenthesized (or, import lists could equally well 
be in layout after 'where', 'of', 'let' or 'do' if we adopt the layout 
syntax)


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


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
 current namespace (Map).

Incidentally, I sometimes find myself writing this:

  import Data.Map (Map) ; import qualified Data.Map as M

It's not perfect, but at least it lines up with my other imports a
little better.


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


[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 see any reason of why
one is included and the other is not. Does anyone?

  1. http://www.cs.chalmers.se/~rjmh/QuickCheck/manual.html
  2. http://www.cs.chalmers.se/~rjmh/QuickCheck/manual_body.html#17
-- 
Roman I. Cheplyaka :: http://ro-che.info/
...being in love is totally punk rock...
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 wiki:

 http://www.haskell.org/haskellwiki/Sudoku

 Please add your solver there.

I've done that.  Thanks.

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


[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 also be truncated to before the end of the line by another
--.  For example:

  noncomment -- comment comment
  noncomment -- comment comment -- noncomment noncomment -- comment --
noncomment
  noncomment

I haven't been able to get the TokenParser to work with this style of
comment.  The best I could do was copy the whole Token module and modify the
code:

data LanguageDef st
= LanguageDef
{  {- snip -}
*, commentLine:: String*
   {- snip -}
}

   {- snip -}

makeTokenParser languageDef
= TokenParser{   {- snip -}   }
where
   {- snip -}
  whiteSpace
| noLine  noMulti  = skipMany (simpleSpace *| customComment* ?
)
| noLine = skipMany (simpleSpace *| customComment* |
multiLineComment ? )
| noMulti= skipMany (simpleSpace *| customComment* |
oneLineComment ? )
| otherwise  = skipMany (simpleSpace *| customComment* |
oneLineComment | multiLineComment ? )
where
  noLine  = null (commentLine languageDef)
  noMulti = null (commentStart languageDef)
  *customComment =
do{commentCustom languageDef
  ;return()
}*

Then I put my specialised comment parser in the customComment field:

languageDef = TOKEN.LanguageDef
   {{- snip -}
   , TOKEN.commentCustom = customComment
{- snip -}
   }
   where
  customComment = do
 string --
 untilLineCommentEnd
 return ()

  untilLineCommentEnd = do
 c - manyTill anyChar (string \n | try (string --))
 return ()

Anyone know of a way I could reuse the TokenParser code rather than copy and
tweaking it?

Thanks

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


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 way. Would you suggest using other tools?


Ah, yes, it is common to develop on an FPGA before fabricating to, say, on
ASIC .

 I'm still a total noob in this area

So you plan on developing a chip or board without any previous hardware
experience?  Sounds challenging :).
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 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 also be truncated to before the end of 
the line by another --.  For example:


  noncomment -- comment comment
  noncomment -- comment comment -- noncomment noncomment -- comment -- 
noncomment

  noncomment

I haven't been able to get the TokenParser to work with this style of 
comment.  The best I could do was copy the whole Token module and modify 
the code:


data LanguageDef st 
= LanguageDef

{  {- snip -}
*, commentLine:: String*
   {- snip -}
}

   {- snip -}

makeTokenParser languageDef
= TokenParser{   {- snip -}   }
where
   {- snip -}
  whiteSpace
| noLine  noMulti  = skipMany (simpleSpace *| customComment* 
? )
| noLine = skipMany (simpleSpace *| customComment* 
| multiLineComment ? )
| noMulti= skipMany (simpleSpace *| customComment* 
| oneLineComment ? )
| otherwise  = skipMany (simpleSpace *| customComment* 
| oneLineComment | multiLineComment ? )

where
  noLine  = null (commentLine languageDef)
  noMulti = null (commentStart languageDef)
  *customComment =
do{commentCustom languageDef
  ;return()
}*

Then I put my specialised comment parser in the customComment field:

languageDef = TOKEN.LanguageDef
   {{- snip -}
   , TOKEN.commentCustom = customComment
{- snip -}
   }
   where
  customComment = do
 string --
 untilLineCommentEnd
 return ()

  untilLineCommentEnd = do
 c - manyTill anyChar (string \n | try (string --))
 return ()

Anyone know of a way I could reuse the TokenParser code rather than copy 
and tweaking it?


Thanks

-John




___
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


[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 done declarative
with statemachines and workflows (not handcoded, dut drawed) all other with
functions. Has somebody experience with this? Or is that a bad idea? Should
I use pure functions, or imperative-functional language such as Scala? Is
somebody here using CAL (OpenQuark) in jee application? What is your
experience
-- 
View this message in context: 
http://www.nabble.com/CAL-%28OpenQuark%29-and-enterprise-tp18366397p18366397.html
Sent from the Haskell - Haskell-Cafe mailing list archive at Nabble.com.

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


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
 
  I dislike the fact that ,'s come after every line but the last - it
  lacks consistency, and often requires 1 more line of diff when adding
  somethign (add comma to previous line, and add the line). I would
  rather write:
 
 Also in the current syntax it is allowed to add a comma in the last line.

GHC rejects this.  (Or is that just for import lists?)

jcc


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


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 what you might want to do,


 Should
  I use pure functions, or imperative-functional language such as Scala?

On the Haskell list I think its fair to say everyone recommends you
should use Haskell.

Thanks

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


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 haskell..
 I'm thinking about designing a similar tool to www.combimouse.com.

See also BlueSpec and Atom et al,

http://funhdl.org/wiki/doku.php

http://funhdl.org/wiki/doku.php?id=funhdlDokuWiki=fa52189d5ac4c0098c15ee324e0056ec
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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
unqualified (Map, (\\))
qualified   (lookup, map, null)
hiding  (filter)

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.

-- 
Dave Menendez [EMAIL PROTECTED]
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 developments in the
   [1]Haskell community.

   The [2]ICFP Programming Contest is this weekend! Go forth and kick some
   butt, Haskell-style. A big thank you in advance to all those at PSU and
   U Chicago who are working hard to write and run the contest.

Community News

   Luke Palmer (luqui) is [3]having a great time in Antwerp.

   John Goerzen's son is [4]so cute, it should be illegal.

Announcements

   Haskell-cafe on lively.com. Edward Kmett has created a [5]Haskell Cafe
   room on Google's new virtual-world platform [6]Lively (which is
   unfortunately windows-only at the moment).

   Uniplate 1.2. Neil Mitchell [7]announced the release of [8]Uniplate
   1.2, a library for reducing boilerplate code by performing generic
   traversals. Version 1.2 features some bug fixes, a compatibility layer
   with Compos and SYB, and a 25-50% performance increase over Uniplate
   1.0.

   GHC 6.8.2 stable in Gentoo. Luis Araujo [9]announced that GHC 6.8.2,
   and its accompanying libraries, have now been marked as stable in the
   official Gentoo portage tree.

   The Monad.Reader (11) - Call for Copy. Wouter Swierstra [10]announced a
   call for copy for Issue 11 of [11]the Monad.Reader. The submission
   deadline is August 1, although you should let Wouter know as soon as
   possible if you plan to submit something.

   hCsound. John Lato [12]announced the initial public release of
   [13]hCsound, a Haskell binding to the Csound audio processing language
   API.

   Portland and OSCon. John Goerzen [14]inquired whether any Haskellers in
   Portland would be interested in getting together during OSCon July 23
   or 24.

   Faster graph SCCs. Iavor Diatchki [15]announced that he has implemented
   Tarjan's algorithm for computing the strongly connected components of a
   graph, which is considerably faster than the containers package for
   larger graphs. Iavor's implementation is available in the [16]GraphSCC
   package.

   parallel map/reduce. jinjing [17]exhibited some code for doing parallel
   map/reduce computations.

   Disciplined Disciple Compiler. Ben Lippmeier [18]announced version 1.1
   of the [19]Disciplined Disciple Compiler (DDC), an explicitly lazy
   dialect of Haskell, with support for first class destructive update of
   arbitrary data, computational effects without the need for state
   monads, and type directed field projections. Version 1.1 includes a
   number of new features and more example code.

   darcs 2.0.2. David Roundy [20]announced the release of [21]darcs 2.0.1
   and 2.0.2. These releases fix quite a few bugs, and users of darcs 2
   are strongly recommended to upgrade.

Google Summer of Code

   Progress updates from participants in the 2008 [22]Google Summer of
   Code.

   GHC plugins. Max Bolingbroke is working on dynamically loaded plugins
   for GHC. Over the [23]past two weeks, he has implemented type safe
   dynamic loading, an annotations system, and some sample plugins.

   Hoogle 4. Neil Mitchell (ndm) is working on [24]Hoogle 4. [25]This
   week, he has been working on type searching, using a much more
   efficient algorithm than type search in previous versions of Hoogle.
   Next week, he plans to finish off type search and work on the build
   system.

   DPH physics engine. Roman Cheplyaka (Feuerbach) is working on a
   [26]physics engine using [27]Data Parallel Haskell. He spent most of
   [28]this week fixing bugs and improving existing simulation code. And
   he now has something to [29]show for it!

   Language.C. Benedikt Huber (visq) is [30]working on Language.C, a
   standalone parser/pretty printer library for C99. [31]This week, he
   created a semantic representation for declarations and types, and a way
   to convert between an AST representation and a semantic representation.

   Cabal dependency framework. Andrea Vezzosi (Saizan) is working on a
   [32]make-like dependency analysis framework for Cabal.

   Generic tries. Jamie Brandon is working on a library for efficient maps
   using generalized tries.

   GHC API. Thomas Schilling (nominolo) is working on [33]improvements to
   the GHC API.

Libraries

   Proposals and extensions to the [34]standard libraries.

   Extensible exceptions. Ian Lynagh sent out a [35]proposal to replace
   the current exception mechanism in the base library with extensible
   exceptions, a la Simon Marlow's [36]extensible extensions paper.
   Deadline for discussion is 25th July.

Discussion

   Qualified import syntax badly designed (?). Neil Mitchell began a
   [37]discussion about Haskell syntax for qualified module imports (and
   module imports in general).

   Trouble with zip12. Michael Feathers is [38]having trouble

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 looking for some kind of
  documentation for ~20 minutes and I still can't find an
  example of an import.

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


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) then
Scala would most likely be a very good place to look.

Cheers,


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


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 does fit together logically.

  What does that look like? I've been looking for some kind of
  documentation for ~20 minutes and I still can't find an
  example of an import.

There's a description on their wiki at
http://appserv.cs.chalmers.se/users/ulfn/wiki/agda.php?n=Docs.ModuleSystem.
There's a longer description in chapter 4 of Ulf Norell's thesis,
http://www.cs.chalmers.se/~ulfn/papers/thesis.pdf, which may be
slightly out of date.

Essentially, the import statement in Agda brings a module from another
file into scope as if it were a sub-module in the current file. It
also lets you rename the module, in case it conflicts with another
name. It does not bring any values or types into scope; they are
accessed by qualified names.

import Some.Module
import Some.Other.Module as SOM

A separate statement lets you bring names from any module into the
current scope. You can provide a list of names to include or exclude,
and a list of names to rename.

open SOM using (x,y)
open SOM renaming (x as alsoX, y as alsoY)
open SOM hiding (x,y)

You can combine renaming with using or hiding, but you can't use using
or hiding together. Note that hidden names are still accessible as
qualified names. That is, if you open SOM hiding x, you can still say
SOM.x.

There's also a short-hand form that lets you import a module and open
it on the same line.

Aside from the syntax differences, Agda's module system features
nested modules and parameterized modules, both of which could be
pretty handy in Haskell.

Nested modules allow libraries which have many modules with similar
names to use qualified names.

open import Gtk using (module Button, module Window)

f = ... Button.name ... Window.name ...

Parameterized modules work sort of like implicit arguments. I suspect
that having them in Haskell could eliminate most of the call for
things like top-level IORefs.

-- 
Dave Menendez [EMAIL PROTECTED]
http://www.eyrie.org/~zednenem/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 and I still can't find an
  example of an import.

 There's a description on their wiki at
 http://appserv.cs.chalmers.se/users/ulfn/wiki/agda.php?n=Docs.ModuleSystem.

  Thanks. That system is pretty neat -- I wish we had it.
  Without parameterized modules, we are reduced to a kind of
  warty singleton pattern -- or IORefs, as you mention.

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


[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, 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 of a data type declaration
   at Planning/Wouter.hs:77:0-42

Any hints?

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


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 of a data type declaration
   at Planning/Wouter.hs:77:0-42

The Data class has a requirement that any instances are also instances
of Typeable, so you'd really want

 data ... = ...  deriving (Data, Typeable)

Except that I couldn't derive Typeable for your particular data type.

It isn't immediately obvious to me that the Typeable family of
classes deal at all with higher-kinded type constructors, but I didn't
look that hard.

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


[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 loop until the user
stops providing valid numbers.  I also need to be able to do IO after
my loop exits.

Consider the following code:
--
module Main
where

import Control.Monad.Fix
import System.IO.Unsafe

promptInt :: String - IO (Maybe Int)
promptInt p = do
  putStr p
  s - getLine
  let rs =  reads s
  if not $ null rs
then return $ Just $ fst $ head rs
else return $ Nothing

promptInts :: [String] - IO [Int]
promptInts [] = return []
promptInts (p:ps) = do
  m - promptInt p
  case m of
Just n - do
   ns - unsafeInterleaveIO $ promptInts ps
   return $ n:ns
Nothing - return []

-- assume accumulator is an opaque function
accumulator :: [Int] - [Int]
accumulator = scanl (+) 0

makeAccPrompt :: Int - String
makeAccPrompt n = [Acc =  ++ show n ++ ] ? 

main :: IO ()
main = do
  xs - mfix $ promptInts . map makeAccPrompt . accumulator
  seq (length xs) $ print xs
--

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?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[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 seconds
for a 640x480 px image with 400 depth of field. This is at worst
122,880,000 calculations (if the scene is rather empty) of a
coordinate of a point in space and then checking for a color. And 60
seconds look really a lot to me for that.

So I went profiling and found out that the strange part of code is the
main color checking function which has a list of objects (at this time
the list is hardcoded). It looks like this:

world :: SpacePoint - VoxelColor
world point = case msum . sequence elements $ point of
Just v  - v
Nothing - noColor
  where elements = [redSphere (0,50,0) 50, greenSphere (25,-50,0) 50,
blueSphere (-150,0,150) 50]

So three spheres in a world and I check if the point is in any of
them. Like that:

sphere :: SpacePoint - BasicReal - VoxelColor - WorldElement --
center of sphere, it's radius, it's color
sphere (x0,y0,z0) r color (x,y,z)
  | x' * x' + y' * y' + z' * z' = r * r = Just color
  | otherwise= Nothing
where x' = x - x0
  y' = y - y0
  z' = z - z0

redSphere :: SpacePoint - BasicReal - WorldElement
redSphere c r = sphere c r redColor

So profiling told me that world function takes 38.4 % of all running
time. So I decided to play with it. Maybe a more direct approach would
be better:

world :: SpacePoint - VoxelColor
world point = findColor [redSphere (0,50,0) 50, greenSphere (25,-50,0)
50, blueSphere (-150,0,150) 50]
  where findColor [] = noColor
findColor (f:fs) = case f point of
Just v  - v
Nothing - findColor fs

Great, it improved. To 40 s. But still it was too much. I tried this:

world :: SpacePoint - VoxelColor
world point = case redSphere (0,50,0) 50 point of
Just v  - v
Nothing - case greenSphere (25,-50,0) 50 point of
 Just v  - v
 Nothing - case blueSphere (-150,0,150) 50 point of
  Just v  - v
  Nothing - noColor

And it took 15 s. And also the profiling was like I would anticipate.
Calculating points coordinates and checking spheres takes almost all
time.

So any suggestions how could I build a list of objects to check at
runtime and still have this third performance? Why this big
difference?

(I am using GHC 6.8.3 with -O2 compile switch.)

(The * operator is casting a ray, that is multiplying a ray direction
vector with a scalar factor.)


Mitar


Main-case.prof
Description: Binary data


Main-rec.prof
Description: Binary data


Main-seq.prof
Description: Binary data
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


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 first (n-1)
elements of xs, you have this identity:

   f xs !! n == f (take (n-1) xs) !! n

You can then call f with a new list each time, extracting the desired
elements as you build up the source list.  This is, of course,
terribly inefficient.

In order to see why you need an unsafe primitive to solve this
function, you may find it enlightening to try to write this function:

 data Stream a b = NilStream | Stream b (a - Stream a b)
 liftStream :: ([a] - [b]) - Stream a b
 liftStream = ?

(the inverse of this function is trivial to write)

The problem is that there is no way to extract the continuation from f
(x:??); if you had some way, you'd be able to call the same
continuation multiple times with different arguments, effectively
pausing f partway through and giving it new input.

By using unsafeInterleaveIO, you are adding a side-effect to the
pure argument to f, which allows it to interact with the user.  Once
that side-effect executes, the value is 'fixed' into place and can't
be modified.

Another way to look at it is to suppose that f didn't meet your
invariant, and tried to access an element out of order.  How is the
thunk to be evaluated for that element built?  If it can't do IO, it
must be a pure computation.  But it needs to do IO because the element
hasn't been determined yet.

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