[Haskell-cafe] Re: [Haskell] ANNOUNCE: Visual Haskell prerelease 0.2

2006-11-30 Thread Johannes Waldmann

  Not only the interfaces [Visual Studio vs. Eclipse]
  are completely different, but an entirely new
  set of interoperability problems would need to be solved. ...

I still don't see what would be the fundamental difference.

(Except perhaps that the Eclipse interfaces are easily available
and well documented so it is at least possible to describe
the interface problems...)

The main advantage (Visual Haskell  over eclipsefp) at the moment
is that VH uses incremental (on-the-fly) typechecking/compilation
while eclipsefp calls the compiler for whole modules?

What source text transformations (refactorings) does VH support?

Best regards,
-- -- Johannes Waldmann -- Tel/Fax (0341) 3076 6479/80 -- 
http://www.imn.htwk-leipzig.de/~waldmann/ ---
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [Haskell] Defining Cg, HLSL style vectors in Haskell

2006-11-30 Thread Slavomir Kaslev

On 11/29/06, Krasimir Angelov [EMAIL PROTECTED] wrote:

It is possible of course but your definition doesn't correspond to any
operation in the usual vector algebra. By the way how do you define
(*)? Isn't it 3D vector multiplication?



(*) is per component multiplication, as it is in Cg/HLSL. For vector
to vector, vector to matrix, etc. multiplication there is mul.

Cheers.

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


Re: [Haskell-cafe] Haskell source transformer?

2006-11-30 Thread Neil Mitchell

Hi Dimitry,


I know there is a Haskell syntax parser around (maybe, more than one).
Does anybody know of any utility based on such parser that does things
I need, or rather a library on top of the parser? I just would like to
avoid reinventing the wheel.


I have a Haskell parser here:
http://www.cs.york.ac.uk/fp/darcs/catch/src/Haskell/ - originally from
GHC but modified slightly by the Hacle project to work in Hugs and be
Haskell 98 (I think).

I am also intending to write a Yhc.Parser library, but haven't got
round to that yet.

Thanks

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


Re: [Haskell] Re: [Haskell-cafe] SimonPJ and Tim Harris explain STM - video

2006-11-30 Thread Chris Kuklewicz
Eureka,

I claim to have written an implementation which agrees with all the semantics
that Simon Peyton-Jones wants for onCommit/onRetry/retryWith.  See below:

Simon Peyton-Jones wrote:
 | In many useful cases, such as the getLine example, the Y action will have 
 its
 | own atomic {} block.  In which case the semantics of when it is allowed to
 | re-attempt X are what is important.  If you require (Y) to complete before
 | re-attempting (X) then you get an infinite regression where every (atomic 
 block)
 | fails with (retryWith (next atomic block)), and nothing is ever 
 re-attempted.
 | This is why retryWith Y meaning rollback X and do Y  atomic X is the 
 wrong
 | implementation.
 
 I don't agree. I think it's quite reasonable. Not many atomic blocks will
 finish with retryWith. Of course there is a possibility of an infinite loop, 
 but
 we already have that: f x = f x. Of course, Y can always choose to do a 
 forkIO,
 but it shouldn't hav to.
 
 For me the only difficulty is the implementation. We'd like to block X on the
 TVars it read (as usual), *unless* executing Y wrote to any of them. That
 requires a bit more cleverness in the commit code, but not a great deal I 
 think.
 
 Simon

It is the Helper Thread code version on the wiki at
http://haskell.org/haskellwiki/New_monads/MonadAdvSTM#Helper_Thread_Code

Quick explanation of the code for runAdvSTM (usually called with atomicAdv):

When the action X in (atomicAdv X) ends with (retryWith Y) the job Y is put into
an MVar.  Then a retry causes the orElse in wrappedAction to perform
check'retry.  This sees the job Y and then
 *) if this is the first retry job: creates and cache a channel and spawn the
helper thread
 *) push the retry job Y into the channel
 *) call retry to cause action X to cause the current GHC runtime to block on
whatever STM-variables it used

The wrappedAction commits if and only if the action X commits.  In which case
the commit action stored in the TVar is read and performed.  Then a check is
performed to see if the helper thread was spawned, and if so tell the helper
thread to quit and block until the helper thread is done.

Note that the action X can be re-attempted by the runtime before the retry job Y
is run or before it has finished running.  But this will only happen in the
usual cases where there was an STM update, instead of the possible busy wait in
the Single Thread code example on the wiki page.

Does this meet your specifications, Simon?

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


[Haskell-cafe] Re: Difficult memory leak in array processing

2006-11-30 Thread apfelmus
Duncan Coutts wrote:
 On Wed, 2006-11-29 at 20:27 +0100, [EMAIL PROTECTED] wrote:
 
 On the implementation level, lazy evaluation is in the way when
 crunching bytes.
 
 Something I rather enjoyed when hacking on the ByteString lib is finding
 that actually lazy evaluation is great when crunching bytes, though you
 do need to know exactly when to use it.
 
 Lazy ByteStrings rely on lazy evaluation of course. Demanding a lazy
 ByteString alternates between strictly filling in big chunks of data in
 memory with lazily suspending before producing the next chunk.
 
 As many people have observed before, FP optimisation is to a great
 extent about thinking more carefully about a better evaluation order for
 a computation and making some bits stricter and some bits lazier to get
 that better evaluation order.

I completely agree. My statement was not well formulated, I actually
meant that the overhead implied by lazy evaluation occurring at every
single byte to be crunched is in the way. In this case, the cost is too
high to pay off as the bytes are most likely consumed anyway. The
detailed account keeping about every byte (is it _|_ or not?) is
unnecessary for a (map) which invariably does look at every byte. The
situation is already different for a (fold), though:

any p = foldr (\x b - p x `or` b) False

Here, the computation may stop at any position in the list.

In a sense, lazy ByteStrings just reduce the cost of lazy evaluation /
byte ratio by grouping bytes strictly. Bookkeeping becomes cheaper
because one doesn't look up so often. Of course, with a stricter fold,
(any) gets more costly. The aim is to make the former ratio smaller
while not raising the latter too much. One may say that ByteString makes
explicit what the Optimistic Haskell Compiler aimed to make implicit.

IMHO, lazy evaluation is always the better choice (in theory). In
practice, the only problem about lazy evaluation is the overhead (which
hurts mostly at (large - small)) which is *not* a consequence of no
free lunch but stems from the fact that current machine architecture is
not very friendly to purely functional things. In a sense, the natural
complexity measure in Haskell is the number of reductions in hugs +s
whereas the natural complexity measure on RAM machines is the number of
operations in 0xDEADBEAF-arithmetic. Unfortunately, it's the latter
which is inside Intel.

Regards,
apfelmus

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


Re: [Haskell-cafe] Re: [Haskell] ANNOUNCE: Visual Haskell prerelease 0.2

2006-11-30 Thread Thiago Arrais

On 11/30/06, Johannes Waldmann [EMAIL PROTECTED] wrote:

The main advantage (Visual Haskell  over eclipsefp) at the moment
is that VH uses incremental (on-the-fly) typechecking/compilation
while eclipsefp calls the compiler for whole modules?


I would say this is one of the greatest advantages of VH, don't know if it is
the main one, but it surely is an advantage. I wonder how VH achieves that.
I imagine it manages to run GHC (it uses GHC, right?) inside the .Net VM
or at least access it through some programmatic interface using some kind
of native/VM data conversion. GHC code (and not VH code) do the
typechecking/compilation tricks. Is that right?

Eclipse is Java and I am pretty sure we can do something similar with it
and we actually did something like the second approach prior to version
0.9.1, but just for source code parsing. What do we need for that?

Cheers,

Thiago Arrais
--
Mergulhando no Caos - http://thiagoarrais.wordpress.com
Pensamentos, idéias e devaneios sobre desenvolvimento de software e
tecnologia em geral
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] generating javascript

2006-11-30 Thread Joel Björnson

2006/11/30, jeff p [EMAIL PROTECTED]:


Is the JavaScript embedding in HSPClientside essentially the same as
the embedding explained in Broberg's thesis?



Yes, in principal the core modules are based on the thesis.
Combinators and higher level functions are built on top of these.

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


Re: [Haskell-cafe] Re: [Haskell] ANNOUNCE: Visual Haskell prerelease 0.2

2006-11-30 Thread Krasimir Angelov

VSHaskell isn't interfacing with .NET but is a COM server written in
Haskell. The VStudio IDE is actually implemented in C but is using COM
as an interface to the various plugins. That way you can implement the
plugin in C++/.NET/Haskell or what ever you want. For Eclipse you need
a bridge between JVM and Haskell. In addition you have find some way
to build .so library for Linux.

Cheers,
 Krasimir


On 11/30/06, Thiago Arrais [EMAIL PROTECTED] wrote:

On 11/30/06, Johannes Waldmann [EMAIL PROTECTED] wrote:
 The main advantage (Visual Haskell  over eclipsefp) at the moment
 is that VH uses incremental (on-the-fly) typechecking/compilation
 while eclipsefp calls the compiler for whole modules?

I would say this is one of the greatest advantages of VH, don't know if it is
the main one, but it surely is an advantage. I wonder how VH achieves that.
I imagine it manages to run GHC (it uses GHC, right?) inside the .Net VM
or at least access it through some programmatic interface using some kind
of native/VM data conversion. GHC code (and not VH code) do the
typechecking/compilation tricks. Is that right?

Eclipse is Java and I am pretty sure we can do something similar with it
and we actually did something like the second approach prior to version
0.9.1, but just for source code parsing. What do we need for that?

Cheers,

Thiago Arrais
--
Mergulhando no Caos - http://thiagoarrais.wordpress.com
Pensamentos, idéias e devaneios sobre desenvolvimento de software e
tecnologia em geral
___
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] Re: Lazy data from pipe using MissingH module

2006-11-30 Thread John Goerzen
Dougal Stanton wrote:

 Newbie here working on a little program for fetching podcasts. I've been
 using the MissingH.Cmd module in concert with curl to download the RSS
 feeds like this:

First off, check out http://quux.org/devel/hpodder -- it is a podcast
downloader written in Haskell that uses MissingH.Cmd.  And Curl,  Might
just do what you want.

 fetchFeed :: Subscription - IO (Either Error [Episode])
 fetchFeed sub = do
 (pid, feed)  - pipeFrom curl (curlOpts ++
  [--url, (slocation sub)])
 let eps = parseEpisodes (stitle sub) feed
 forceSuccess pid
 return eps
 
 According to the API docs I have to forceSuccess pid *after* I use the
 data. Will this construct do that, or does the compiler have free reign
 to move the line beginning 'let ...' wherever it feels?

No, it won't.  I'd suggest adding something like:

  evaluate (length eps) 

before the forceSuccess.

What happens is that, since Haskell is lazy, it won't actually consume the
data from the pipe until it is needed -- which looks like it could even be
after this function returns.

forceSuccess waits for the process to die.  The process won't die until
you've consumed all its output.  Therefore your program will hang at
forceSuccess.

-- John


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


[Haskell-cafe] Re: The Future of MissingH

2006-11-30 Thread John Goerzen
Bulat Ziganshin wrote:

Hi Bulat,

Many thanks for the *great* comments.

 first, is it possible to integrate MissingH inside existing core libs,
 i.e. Haskell libs supported by Haskell community? i think that it will
 be impossible if MissingH will hold its GPL status. i think that
 such fundamental library as MissingH should be BSDified to allow use
 it both in commercial and non-commercial code

As others have pointed out, the GPL is not a commercial vs. non-commercial
license.

That said, I am scrupulous about copyrights and licensing.  I know exactly
which bits of MissingH I own the copyright to, and which bits are under
which license.

I have, for quite some time already, maintained an LGPL branch of MissingH. 
This branch contains all of the code in MissingH that is:

a) compatible with the LGPL
b) not depending on LGPL-incompatible components

That means basically the code I wrote, plus any LGPL or BSD code others
wrote.

It would be easy enough to figure out which bits can suitably fall under BSD
license; it would be nearly the same bits as can fall under LGPL.  Again,
since I own copyright to most of the code, I can put it under as many
different licenses as I like, so long as I respect everyone else's
copyrights properly.

In any case, most of the stuff that would be suitable for base was written
by me anyway.

 if library will be BSDified, and somewhat advertized. i hope that
 its parts will start moving to the more specific libs of core set, say
 HVFS system into the Files library, logging facilities into the Unix
 library, so on

Planning to do so.

 quality of code documenting in your lib, most peoples prefer to read
 Haddocks, which again should be made available on web

Already are, and will continue to be.

 next, while you accept patches to the lib, this's not declared in your
 announces. best way is just to open darcs repository - most peoples
 thinks that having darcs repository and accepting patches is the same
 thing :)  i can also propose you the idea that Pupeno, packager of

Have it, but it's under-documented.  That will change.

See http://software.complete.org/offlineimap/ for an example of what I
intend to do with MissingH as well.

 Streams library used - he included in the tgz files copy of darcs
 repository, again facilitating use of darcs and developing new patches
 for library

That is an interesting idea, but the MissingH repo has nearly 1000 darcs
patches by now.  This would seriously bloat the tarball, plus it's easy
enough to just download it off the 'net with darcs.

 and, about WindowsCompat.hs - stat() function is available on Windows
 and even used to implement getModificationTime :)

Err, how?  Is this new in ghc 6.6?  Last I tried, -package unix wouldn't
even work on Windows.

   I initially wrote it that way to make resolving dependencies easier
   for end users.
 
 now Cabal handles this

No, it just complains when dependencies aren't resolved.  People still have
to go out and download/install each piece manually.


-- John


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


Re: [Haskell-cafe] [Redirect] polymorphism and existential types

2006-11-30 Thread Roberto Zunino

Donald Bruce Stewart wrote:

Supposing a polymorphic value (of type, say, forall a . ExpT a t) is
stored inside an existential package (of type, say, forall a . Exp a),
I wonder how to recover a polymorphic value when eliminating the
existential.  The ``natural way'' to write this doesn't work:

{-# OPTIONS -fglasgow-exts #-}

data ExpT a t
data Exp a = forall t . Exp (ExpT a t)

f :: (forall a . ExpT a t) - ()
f e = ()

g :: (forall a . ExpT a t) - ()
g e =
  let e1 :: forall a . Exp a
  e1 = Exp e
  in case e1 of
   Exp e' - f e'


IIUC, this is not possible. I believe that the type given for e1 is 
strictly weaker than the type of e, so that recovering the type of e 
from that of e1 can not be done. This is because (up-to iso)


e :: exists t . forall a . ExpT a t
e1:: forall a . exists t . ExpT a t

Clearly, the first one (where t is fixed) is stronger than the second, 
(where t might depend on a).


Regards,
Roberto Zunino.


signature.asc
Description: OpenPGP digital signature
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] New Name for MissingH?

2006-11-30 Thread John Goerzen
Quick feedback time...

One comment people made in the Future of MissingH thread was that the name
isn't very suggestive of what the library does.

I'm planning to follow the advice of many people and split the major
MissingH components off into smaller bits (ConfigParser, HVFS, etc). 
MissingH itself will then contain any small utility functions (probably
mainly string and list-related) that for whatever reason aren't suitable to
go into base.

What should it be called?  Should it keep the MissingH name?

The alternative I've been thinking of is something like Haskell Utility
Library (HUL).

Ideas?

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


Re: [Haskell-cafe] New Name for MissingH?

2006-11-30 Thread Neil Mitchell

Hi


The alternative I've been thinking of is something like Haskell Utility
Library (HUL).


Yuk. I like MissingH. MissingH suggests things that are missing from
the standard set and provided here. HsMissing would be my preferred
choice, but its not really important.

Haskell says which language its written in, library says its a
library, and utility tells me nothing (the word is too overloaded). By
the end I know its a Haskell library...

I think the problem isn't that the name is confusing, but that no one
knows it exists or what it does. Things like adding it to the Hoogle
database would probably help, along with greater there is a function
for that in MissingH posts to the haskell-cafe list as people ask.

Thanks

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


RE: [Haskell-cafe] Re: [Haskell] ANNOUNCE: Visual Haskell prerelease0.2

2006-11-30 Thread Bayley, Alistair
(not sure if this is the best place for questions about VisualHaskell)

I've just installed VisualHaskell, and I've noticed that some of the
hierarchical libraries are missing/hidden:
 - Control.Monad.State (and other chunks of the Control.Monad hierarchy,
like Control.Monad.Error/Identity/List/Trans)
 - Test.HUnit (in fact Test.* is gone)

and I'm sure there's plenty more missing.

?

Alistair
*
Confidentiality Note: The information contained in this message,
and any attachments, may contain confidential and/or privileged
material. It is intended solely for the person(s) or entity to
which it is addressed. Any review, retransmission, dissemination,
or taking of any action in reliance upon this information by
persons or entities other than the intended recipient(s) is
prohibited. If you received this in error, please contact the
sender and delete the material from any computer.
*
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re[2]: [Haskell-cafe] New Name for MissingH?

2006-11-30 Thread Bulat Ziganshin
Hello Neil,

Thursday, November 30, 2006, 5:06:55 PM, you wrote:

 I think the problem isn't that the name is confusing, but that no one
 knows it exists or what it does. Things like adding it to the Hoogle
 database would probably help, along with greater there is a function
 for that in MissingH posts to the haskell-cafe list as people ask.

there is one idea: one shouldn't have internet access to be able to
use Haskell effectively. so, good organization and proper names would
be useful

-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re[2]: [Haskell-cafe] New Name for MissingH?

2006-11-30 Thread Philippa Cowderoy
On Thu, 30 Nov 2006, Bulat Ziganshin wrote:

 there is one idea: one shouldn't have internet access to be able to
 use Haskell effectively. so, good organization and proper names would
 be useful
 

In that vein, Hoogle as an offline tool probably helps. I should play with 
it sometime.

-- 
[EMAIL PROTECTED]

My religion says so explains your beliefs. But it doesn't explain
why I should hold them as well, let alone be restricted by them.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Command line utility that shrinks/simplifies functions applications ?

2006-11-30 Thread Nicola Paolucci

Hi All!

Haskell newbie here with a very simple question because google and
hoogle are of no help.

On the IRC channel #haskell (which I cannot access now from work) I
saw somebody using a tool which automatically simplifies
expressions,composition of multiple functions to the bare minimum. It
was a query to lambdabot I think.

Is that tool/library also standalone ? What's its name ? Where can I find it ?
That really rocked ...

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


Re: [Haskell-cafe] Command line utility that shrinks/simplifies functions applications ?

2006-11-30 Thread Bulat Ziganshin
Hello Nicola,

Thursday, November 30, 2006, 5:32:46 PM, you wrote:

 On the IRC channel #haskell (which I cannot access now from work) I
 saw somebody using a tool which automatically simplifies
 expressions,composition of multiple functions to the bare minimum.

it is the IRC channel itself


-- 
Best regards,
 Bulatmailto:[EMAIL PROTECTED]

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


Re: [Haskell-cafe] New Name for MissingH?

2006-11-30 Thread Clifford Beshers


John Goerzen wrote:

Quick feedback time...

One comment people made in the Future of MissingH thread was that the name
isn't very suggestive of what the library does.


My colleague uses modules called `My' to hold functions that seem like 
they should be in a library, but which aren't yet mature enough to be 
promoted.
I've always thought of MissingH the same way.  It would make a good 
place for new functions like intercalate to be placed while they are 
being considered.


But eventually, good functions and modules should graduate.  
ConfigParser and HVFS are good candidates to be standalone libraries, as 
you say.  I've been meaning to submit the 'merge' function that we sent 
you, as well.


If MissingH acted as a general waystation, we could keep a stable 
library base installed on our systems, but get the latest that people 
are talking about by pulling in that one package.


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


Re: [Haskell-cafe] Command line utility that shrinks/simplifies functions applications ?

2006-11-30 Thread Spencer Janssen
I believe you're talking about the `pl' plugin for lambdabot.   
Lambdabot has an offline mode, visit the homepage for the source:

http://www.cse.unsw.edu.au/~dons/lambdabot.html

There is also a web interface to lambdabot, but I can't seem to find  
the link.



Cheers,
Spencer Janssen

On Nov 30, 2006, at 8:32 AM, Nicola Paolucci wrote:


Hi All!

Haskell newbie here with a very simple question because google and
hoogle are of no help.

On the IRC channel #haskell (which I cannot access now from work) I
saw somebody using a tool which automatically simplifies
expressions,composition of multiple functions to the bare minimum. It
was a query to lambdabot I think.

Is that tool/library also standalone ? What's its name ? Where can  
I find it ?

That really rocked ...

Thanks,
   Nick
___
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] Command line utility that shrinks/simplifies functions applications ?

2006-11-30 Thread Nicola Paolucci

Hi Spencer,

On 11/30/06, Spencer Janssen [EMAIL PROTECTED] wrote:

I believe you're talking about the `pl' plugin for lambdabot.
Lambdabot has an offline mode, visit the homepage for the source:
http://www.cse.unsw.edu.au/~dons/lambdabot.html


That's exactly what I was looking for!
Thank you very much !

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


[Haskell-cafe] Re: New Name for MissingH?

2006-11-30 Thread John Goerzen
Neil Mitchell wrote:

 Hi
 
 The alternative I've been thinking of is something like Haskell Utility
 Library (HUL).
 
 Yuk. I like MissingH. MissingH suggests things that are missing from
 the standard set and provided here. HsMissing would be my preferred
 choice, but its not really important.

Makes sense.

 I think the problem isn't that the name is confusing, but that no one
 knows it exists or what it does. Things like adding it to the Hoogle

I'm working on that.  There should be a real homepage with a wiki for it
soon.  It's already in HCAR, and I think it's on the wiki list of
libraries.  But I'll try to help it along, too.

I couldn't figure out how to add it to hoogle.  Does anyone have a pointer
for that?

 database would probably help, along with greater there is a function
 for that in MissingH posts to the haskell-cafe list as people ask.

True, too.  I didn't want to be too annoying, so I have tried to not do that
too much.  But since you asked, I'll try to step in more.

-- John


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


Re: [Haskell-cafe] Command line utility that shrinks/simplifies functions applications ?

2006-11-30 Thread Pepe Iborra


On 30/11/2006, at 17:04, Spencer Janssen wrote:

I believe you're talking about the `pl' plugin for lambdabot.   
Lambdabot has an offline mode, visit the homepage for the source:

http://www.cse.unsw.edu.au/~dons/lambdabot.html

There is also a web interface to lambdabot, but I can't seem to  
find the link.


http://lambdabot.codersbase.com/

It's really nice, I use it all the time.___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: New Name for MissingH?

2006-11-30 Thread Neil Mitchell

Hi


I couldn't figure out how to add it to hoogle.  Does anyone have a pointer
for that?


Wait for Hoogle 4, and bug me. Hoogle 4 will allow additional
libraries to be searched. Once its ready I'll add MissingH.


 database would probably help, along with greater there is a function
 for that in MissingH posts to the haskell-cafe list as people ask.

True, too.  I didn't want to be too annoying, so I have tried to not do that
too much.  But since you asked, I'll try to step in more.


I think its a great way to both promote MissingH, and help newcomers
at the same time.

Thanks

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


Re: [Haskell-cafe] Re: [Haskell] ANNOUNCE: Visual Haskell prerelease0.2

2006-11-30 Thread Krasimir Angelov

Hi Alistair,

Visual Haskell is packaged with just the core libraries.
Control.Monad.* modules are part of mtl and Test.HUnit is part of
HUnit which aren't core libraries and aren't installed. It was long
time ago when I was using the official Windows installer for last
time. Is it still packaged with all libraries?

Krasimir


On 11/30/06, Bayley, Alistair [EMAIL PROTECTED] wrote:

(not sure if this is the best place for questions about VisualHaskell)

I've just installed VisualHaskell, and I've noticed that some of the
hierarchical libraries are missing/hidden:
 - Control.Monad.State (and other chunks of the Control.Monad hierarchy,
like Control.Monad.Error/Identity/List/Trans)
 - Test.HUnit (in fact Test.* is gone)

and I'm sure there's plenty more missing.

?

Alistair
*
Confidentiality Note: The information contained in this message,
and any attachments, may contain confidential and/or privileged
material. It is intended solely for the person(s) or entity to
which it is addressed. Any review, retransmission, dissemination,
or taking of any action in reliance upon this information by
persons or entities other than the intended recipient(s) is
prohibited. If you received this in error, please contact the
sender and delete the material from any computer.
*
___
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] Re: [Haskell] ANNOUNCE: Visual Haskell prerelease 0.2

2006-11-30 Thread Krasimir Angelov

Hi Shelarcy,

Could you check whether you have this registry key:

HKEY_LOCAL_MACHINE\SOFTWARE\Microsoft\VisualStudio\8.0\InstallDir

and tell me its value? Typically its value should be such that the
following script to work.

Set shell = CreateObject(WScript.Shell)
vstudioPath  = shell.RegRead
 (HKEY_LOCAL_MACHINE\SOFTWARE\Microsoft\VisualStudio\8.0\InstallDir)
shell.Run (  vstudioPath  devenv.exe /Setup,0,true)

Cheers,
  Krasimir


On 11/30/06, shelarcy [EMAIL PROTECTED] wrote:

Hi Krasimir,

 On 11/30/06, shelarcy [EMAIL PROTECTED] wrote:
 But ... I can't install Visual Haskell prerelease 0.2. Near
 the end of install process, Microsoft Development Environment
 cause error.
On Thu, 30 Nov 2006 17:03:22 +0900, Krasimir Angelov [EMAIL PROTECTED] wrote:
 Could you tell me what error message you see during the installation?
 If it is in Japan then translate it in English ;-).

It's not good error message. Anyway, I translate it.

Near the end of install process, error dialog opened and says:

---
The problem happende, so exit Microsoft Development Environment.
I'm sorry for causing inconvenience to you.

(under its message, error dialog has form that send error report
for Microsoft or shows error detail. These messages are not
important, so I don't translate that.)
---

And click form that shows error detail, another dialog opened.
It shows:

---
:Error ditail:
An unhandled exception has been caught by the VSW exception filter.
:Error Signature:
AppName: devenv.exe  AppVer: 7.10.6030.0 ModName: unknown
ModVer: 0.0.0.0  Offset: 00bbbacc
:Report Detail:
(Below meassage attetion to user that error report send what.
So these messages are not important, too.)
---

 Also it can help
 if you run the installer with logging:

 $ msiexec VSHaskell71.msi /l log.txt

msiexec doesn't run its command. And error dialog noticed that
you forgot /i optio. So I used below command.

$ msiexec /i VSHaskell71.msi /l log.txt

I think log.txt is much more useful than previous messages.
log.txt also has Japanese messages. So I translated that part.

---
(snip)

Action 20:38:17: CA_RegisterHelpFile.3643236F_FC70_11D3_A536_0090278A1BB8.
   IHxRegisterSession::ContinueTransaction() returned 0.
   Helpfile: C:\Program Files\Visual Haskell\doc\alex.HxS was successfully 
registered to namespace vs_haskell.
elpfile: C:\Program Files\Visual Haskell\doc\building.HxS was successfully 
registered to namespace vs_haskell.
   Helpfile: C:\Program Files\Visual Haskell\doc\Cabal.HxS was successfully 
registered to namespace vs_haskell.
   Helpfile: C:\Program Files\Visual Haskell\doc\haddock.HxS was 
successfully registered to namespace vs_haskell.
   Helpfile: C:\Program Files\Visual Haskell\doc\happy.HxS was successfully 
registered to namespace vs_haskell.
   Helpfile: C:\Program Files\Visual Haskell\doc\libraries.HxS was 
successfully registered to namespace vs_haskell.
   Helpfile: C:\Program Files\Visual Haskell\doc\users_guide.HxS was 
successfully registered to namespace vs_haskell.
   Helpfile: C:\Program Files\Visual Haskell\doc\vh.HxS was successfully 
registered to namespace vs_haskell.
Action 20:38:17: CA_RegisterPlugIn.3643236F_FC70_11D3_A536_0090278A1BB8.
   IHxRegisterSession::ContinueTransaction() returned 0.
   IHxPlugIn::RegisterHelpPlugIn() returned 0.
   Namespace: vs_haskell was successfully plugged into namespace 
MS.VSCC.2003.
Action 20:38:17: CA_CommitHelpTransaction.3643236F_FC70_11D3_A536_0090278A1BB8.
Action 20:38:17: RegisterProduct. Registering product
RegisterProduct: {FEC3263A-9034-49C5-8C5D-902231009894}
Action 20:38:18: PublishFeatures. Publishing Product Features
PublishFeatures: Feature: Complete
Action 20:38:18: PublishProduct. Publishing product information
1: {FEC3263A-9034-49C5-8C5D-902231009894}
Action 20:38:18: RollbackCleanup. Removing backup files
   IHxRegisterSession::ContinueTransaction() returned 0.
   Registration session: {FEC3263A-9034-49C5-8C5D-902231009894} was 
successfully committed.
RollbackCleanup: File: C:\Config.Msi\fc3d12.rbf
RollbackCleanup: File: C:\Config.Msi\fc3d13.rbf
RollbackCleanup: File: C:\Config.Msi\fc3d14.rbf
RollbackCleanup: File: C:\Config.Msi\fc3d15.rbf
RollbackCleanup: File: C:\Config.Msi\fc3d16.rbf
Action ended 20:38:18: InstallFinalize. Return value 1.
Action 20:38:18: CA_HxMerge_VSCC.3643236F_FC70_11D3_A536_0090278A1BB8.
Action start 20:38:18: CA_HxMerge_VSCC.3643236F_FC70_11D3_A536_0090278A1BB8.
tion ended 20:40:09: CA_HxMerge_VSCC.3643236F_FC70_11D3_A536_0090278A1BB8. 
Return value 1.
Action 20:40:09: CA_RemoveTempHxDs.3643236F_FC70_11D3_A536_0090278A1BB8.
Action start 20:40:09: CA_RemoveTempHxDs.3643236F_FC70_11D3_A536_0090278A1BB8.
Action ended 20:40:09: CA_RemoveTempHxDs.3643236F_FC70_11D3_A536_0090278A1BB8. 
Return value 1.
Action 20:40:09: VSHaskellInstall. Register Visual Haskell Plugin
Action start 20:40:09: VSHaskellInstall.
Error 1720. There is a problem with this Windows Installer 

[Haskell-cafe] Re: [Haskell] ANNOUNCE: Visual Haskell prerelease 0.2

2006-11-30 Thread Krasimir Angelov

You can try to setup it manually using the following commands:

$ regsvr32 /i:8.0 /n vs_haskell.dll
$ regsvr32 /i:8.0 /n vs_haskell_babel.dll
$ regsvr32 /i:8.0 /n vs_haskell_dlg.dll
$ devenv.exe /Setup

On 11/30/06, Krasimir Angelov [EMAIL PROTECTED] wrote:

Hi Shelarcy,

Could you check whether you have this registry key:

HKEY_LOCAL_MACHINE\SOFTWARE\Microsoft\VisualStudio\8.0\InstallDir

and tell me its value? Typically its value should be such that the
following script to work.

Set shell = CreateObject(WScript.Shell)
vstudioPath  = shell.RegRead
 (HKEY_LOCAL_MACHINE\SOFTWARE\Microsoft\VisualStudio\8.0\InstallDir)
shell.Run (  vstudioPath  devenv.exe /Setup,0,true)

Cheers,
  Krasimir


On 11/30/06, shelarcy [EMAIL PROTECTED] wrote:
 Hi Krasimir,

  On 11/30/06, shelarcy [EMAIL PROTECTED] wrote:
  But ... I can't install Visual Haskell prerelease 0.2. Near
  the end of install process, Microsoft Development Environment
  cause error.
 On Thu, 30 Nov 2006 17:03:22 +0900, Krasimir Angelov [EMAIL PROTECTED] 
wrote:
  Could you tell me what error message you see during the installation?
  If it is in Japan then translate it in English ;-).

 It's not good error message. Anyway, I translate it.

 Near the end of install process, error dialog opened and says:

 ---
 The problem happende, so exit Microsoft Development Environment.
 I'm sorry for causing inconvenience to you.

 (under its message, error dialog has form that send error report
 for Microsoft or shows error detail. These messages are not
 important, so I don't translate that.)
 ---

 And click form that shows error detail, another dialog opened.
 It shows:

 ---
 :Error ditail:
 An unhandled exception has been caught by the VSW exception filter.
 :Error Signature:
 AppName: devenv.exe  AppVer: 7.10.6030.0 ModName: unknown
 ModVer: 0.0.0.0  Offset: 00bbbacc
 :Report Detail:
 (Below meassage attetion to user that error report send what.
 So these messages are not important, too.)
 ---

  Also it can help
  if you run the installer with logging:
 
  $ msiexec VSHaskell71.msi /l log.txt

 msiexec doesn't run its command. And error dialog noticed that
 you forgot /i optio. So I used below command.

 $ msiexec /i VSHaskell71.msi /l log.txt

 I think log.txt is much more useful than previous messages.
 log.txt also has Japanese messages. So I translated that part.

 ---
 (snip)

 Action 20:38:17: CA_RegisterHelpFile.3643236F_FC70_11D3_A536_0090278A1BB8.
IHxRegisterSession::ContinueTransaction() returned 0.
Helpfile: C:\Program Files\Visual Haskell\doc\alex.HxS was 
successfully registered to namespace vs_haskell.
 elpfile: C:\Program Files\Visual Haskell\doc\building.HxS was 
successfully registered to namespace vs_haskell.
Helpfile: C:\Program Files\Visual Haskell\doc\Cabal.HxS was 
successfully registered to namespace vs_haskell.
Helpfile: C:\Program Files\Visual Haskell\doc\haddock.HxS was 
successfully registered to namespace vs_haskell.
Helpfile: C:\Program Files\Visual Haskell\doc\happy.HxS was 
successfully registered to namespace vs_haskell.
Helpfile: C:\Program Files\Visual Haskell\doc\libraries.HxS was 
successfully registered to namespace vs_haskell.
Helpfile: C:\Program Files\Visual Haskell\doc\users_guide.HxS was 
successfully registered to namespace vs_haskell.
Helpfile: C:\Program Files\Visual Haskell\doc\vh.HxS was successfully 
registered to namespace vs_haskell.
 Action 20:38:17: CA_RegisterPlugIn.3643236F_FC70_11D3_A536_0090278A1BB8.
IHxRegisterSession::ContinueTransaction() returned 0.
IHxPlugIn::RegisterHelpPlugIn() returned 0.
Namespace: vs_haskell was successfully plugged into namespace 
MS.VSCC.2003.
 Action 20:38:17: 
CA_CommitHelpTransaction.3643236F_FC70_11D3_A536_0090278A1BB8.
 Action 20:38:17: RegisterProduct. Registering product
 RegisterProduct: {FEC3263A-9034-49C5-8C5D-902231009894}
 Action 20:38:18: PublishFeatures. Publishing Product Features
 PublishFeatures: Feature: Complete
 Action 20:38:18: PublishProduct. Publishing product information
 1: {FEC3263A-9034-49C5-8C5D-902231009894}
 Action 20:38:18: RollbackCleanup. Removing backup files
IHxRegisterSession::ContinueTransaction() returned 0.
Registration session: {FEC3263A-9034-49C5-8C5D-902231009894} was 
successfully committed.
 RollbackCleanup: File: C:\Config.Msi\fc3d12.rbf
 RollbackCleanup: File: C:\Config.Msi\fc3d13.rbf
 RollbackCleanup: File: C:\Config.Msi\fc3d14.rbf
 RollbackCleanup: File: C:\Config.Msi\fc3d15.rbf
 RollbackCleanup: File: C:\Config.Msi\fc3d16.rbf
 Action ended 20:38:18: InstallFinalize. Return value 1.
 Action 20:38:18: CA_HxMerge_VSCC.3643236F_FC70_11D3_A536_0090278A1BB8.
 Action start 20:38:18: CA_HxMerge_VSCC.3643236F_FC70_11D3_A536_0090278A1BB8.
 tion ended 20:40:09: 
CA_HxMerge_VSCC.3643236F_FC70_11D3_A536_0090278A1BB8. Return value 1.
 Action 20:40:09: CA_RemoveTempHxDs.3643236F_FC70_11D3_A536_0090278A1BB8.
 Action 

Re: [Haskell-cafe] Re: [Haskell] ANNOUNCE: Visual Haskell prerelease 0.2

2006-11-30 Thread Justin Bailey

On 11/30/06, Krasimir Angelov [EMAIL PROTECTED] wrote:


You can try to setup it manually using the following commands:

$ regsvr32 /i:8.0 /n vs_haskell.dll
$ regsvr32 /i:8.0 /n vs_haskell_babel.dll
$ regsvr32 /i:8.0 /n vs_haskell_dlg.dll
$ devenv.exe /Setup



I am having similar problems with the Visual Haskell install, and the
commands given did not help. When I open Visual Studios Help | About dialog,
I get an error about the package failing to initialize. I am installing to
an English copy, however.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Building Binaries with Cabal

2006-11-30 Thread John Goerzen
Hi folks,

I'm in need of some Cabal assistance.

I want to build the unit tests for MissingH using Cabal.  According to the
docs, this should require me to list all of the exposed modules from the
library as other modules to the binary.  Since there are dozens of these, I
thought a simple hook could do the trick.

I tried hooking into the confHook (which I have already used successfully to
add unix as a build-dep on non-Windows platforms), and thought I could
just pull the exposedModules list from the package and add those as
otherModules to the executable.  But it had no effect.

So I tried hooking in to customBuildHook to do the same thing.  Again, no
effect.

Here's the code I've tried.  Suggestions appreciated.

import Distribution.Simple
import Distribution.PackageDescription
import Distribution.Version
import System.Info
import Data.Maybe

winHooks = defaultUserHooks {confHook = customConfHook}

customConfHook descrip flags =
let mydescrip = case System.Info.os of
  mingw32 - descrip
  _ - descrip {buildDepends = 
(Dependency unix AnyVersion) :
buildDepends descrip}
in (confHook defaultUserHooks) mydescrip flags

customBuildHook descrip lbi uh flags =
let myexecutables = map bdfix (executables descrip)
bdfix exe = 
exe {buildInfo = 
 (buildInfo exe) 
   {otherModules = 
exposedModules . fromJust . library $ descrip}}
mydescrip = descrip {executables = myexecutables}
in (buildHook defaultUserHooks) mydescrip flags
  
main = defaultMainWithHooks winHooks



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


[Haskell-cafe] Re: Building Binaries with Cabal

2006-11-30 Thread John Goerzen
I posted a weird version of the code.  Here's the real version.  Same
problem I described, though.

 Distribution.Simple
import Distribution.PackageDescription
import Distribution.Version
import System.Info
import Data.Maybe

winHooks = defaultUserHooks {confHook = customConfHook,
 buildHook = customBuildHook}

customConfHook descrip flags =
let mydescrip = case System.Info.os of
  mingw32 - descrip
  _ - descrip {buildDepends = 
(Dependency unix AnyVersion) :
buildDepends descrip}
in (confHook defaultUserHooks) mydescrip flags

customBuildHook descrip lbi uh flags =
let myexecutables = map bdfix (executables descrip)
bdfix exe = 
exe {buildInfo = 
 (buildInfo exe) 
   {otherModules = 
exposedModules . fromJust . library $ descrip}}
mydescrip = descrip {executables = myexecutables}
in do print mydescrip
  (buildHook defaultUserHooks) mydescrip lbi uh flags
  
main = defaultMainWithHooks winHooks



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


Re: [Haskell-cafe] Building Binaries with Cabal

2006-11-30 Thread Neil Mitchell

Hi


let mydescrip = case System.Info.os of
  mingw32 - descrip
  _ - descrip {buildDepends =


Aghhh! To test if the operating system is windows you
compare against a hard coded string which _isn't_ an OS, but _is_ an
optional component by a 3rd party. It's required to build some Haskell
compilers, but for Yhc and Hugs its not required at any stage, and its
presence is optional!

I know this isn't your fault, it just scares me deeply that os could
return something that isn't an os! How about we add a cpu string,
which returns the amount of RAM installed. Or how about we add a
compiler string, which returns the users surname...

Thanks

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


Re: [Haskell-cafe] Building Binaries with Cabal

2006-11-30 Thread John Goerzen
On Thu, Nov 30, 2006 at 08:53:36PM +, Neil Mitchell wrote:
 Aghhh! To test if the operating system is windows you
 compare against a hard coded string which _isn't_ an OS, but _is_ an
 optional component by a 3rd party. It's required to build some Haskell
 compilers, but for Yhc and Hugs its not required at any stage, and its
 presence is optional!

Your point is well-taken, but the distinction is useful.  If running on
cygwin, my platform is essentially POSIX, even though the OS is Windows.  

And yes, I do claim that this isn't my fault ;-)

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


Re: [Haskell-cafe] Building Binaries with Cabal

2006-11-30 Thread Neil Mitchell

Hi


Your point is well-taken, but the distinction is useful.  If running on
cygwin, my platform is essentially POSIX, even though the OS is Windows.


Yes, but _my_ OS is reported as mingw32, even though its never been
installed on this computer...

Thanks

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


[Haskell-cafe] How to get subset of a list?

2006-11-30 Thread Huazhi (Hank) Gong

Like given a string list s=This is the string I want to test, I want to get
the substring. In ruby or other language, it's simple like s[2..10], but how
to do it in Haskell?
-- 
View this message in context: 
http://www.nabble.com/How-to-get-subset-of-a-list--tf2735647.html#a7631994
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] How to get subset of a list?

2006-11-30 Thread Stefan O'Rear
On Thu, Nov 30, 2006 at 05:47:43PM -0800, Huazhi (Hank) Gong wrote:
 
 Like given a string list s=This is the string I want to test, I want to get
 the substring. In ruby or other language, it's simple like s[2..10], but how
 to do it in Haskell?

Use take and drop, from the Prelude:

(ghci session)
Prelude Hello world
Hello world
Prelude drop 3 Hello world
lo world
Prelude take 7 (drop 3 Hello world)
lo worl
Prelude
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to get subset of a list?

2006-11-30 Thread Huazhi (Hank) Gong

Thanks, it make sense here.
However, like I want to choose s[1,3,6,10] or something like this. Are there
some straightforward function or operator for doing this job? The !!
operator in haskell seems does not support multiple indecies.

Hank

Stefan O wrote:
 
 On Thu, Nov 30, 2006 at 05:47:43PM -0800, Huazhi (Hank) Gong wrote:
 
 Like given a string list s=This is the string I want to test, I want to
 get
 the substring. In ruby or other language, it's simple like s[2..10], but
 how
 to do it in Haskell?
 
 Use take and drop, from the Prelude:
 
 (ghci session)
 Prelude Hello world
 Hello world
 Prelude drop 3 Hello world
 lo world
 Prelude take 7 (drop 3 Hello world)
 lo worl
 Prelude
 ___
 Haskell-Cafe mailing list
 Haskell-Cafe@haskell.org
 http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 

-- 
View this message in context: 
http://www.nabble.com/How-to-get-subset-of-a-list--tf2735647.html#a7632145
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] How to get subset of a list?

2006-11-30 Thread Taral

On 11/30/06, Huazhi (Hank) Gong [EMAIL PROTECTED] wrote:

Thanks, it make sense here.
However, like I want to choose s[1,3,6,10] or something like this. Are there
some straightforward function or operator for doing this job? The !!
operator in haskell seems does not support multiple indecies.


If you're trying to do random access on a list, you should rethink why
you're using a list.

--
Taral [EMAIL PROTECTED]
You can't prove anything.
   -- Gödel's Incompetence Theorem
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to get subset of a list?

2006-11-30 Thread Dan Weston
Your curious example suggests you might be solving a more specialized 
problem, like selecting the diagonal of a flattened matrix. In this 
case, there are much better (and more efficient) data structures that 
enforce invariants (like squareness of a matrix), if that is what you in 
fact are doing.


Taral wrote:

On 11/30/06, Huazhi (Hank) Gong [EMAIL PROTECTED] wrote:

Thanks, it make sense here.
However, like I want to choose s[1,3,6,10] or something like this. Are 
there

some straightforward function or operator for doing this job? The !!
operator in haskell seems does not support multiple indecies.


If you're trying to do random access on a list, you should rethink why
you're using a list.




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


[Haskell-cafe] Re: [Haskell] ANNOUNCE: Visual Haskell prerelease 0.2

2006-11-30 Thread shelarcy
Hi Krasimir,

On Fri, 01 Dec 2006 02:18:19 +0900, Krasimir Angelov [EMAIL PROTECTED] wrote:
 Could you check whether you have this registry key:

 HKEY_LOCAL_MACHINE\SOFTWARE\Microsoft\VisualStudio\8.0\InstallDir

 and tell me its value?

HKEY_LOCAL_MACHINE\SOFTWARE\Microsoft\VisualStudio\7.1\InstallDir
value is C:\Program Files\Microsoft Visual Studio .NET 2003\Common7\IDE\.

 Typically its value should be such that the
 following script to work.

 Set shell = CreateObject(WScript.Shell)
 vstudioPath  = shell.RegRead
   (HKEY_LOCAL_MACHINE\SOFTWARE\Microsoft\VisualStudio\8.0\InstallDir)
 shell.Run (  vstudioPath  devenv.exe /Setup,0,true)

I saw your message, then I checked vshaskell darcs repository
and I saw vs_haskell_setup/setup.vbs.

Okay, I know I forgot to tell popup message what made by VBScript.
I saw just one popup message. It says Failed to setup VStudio.


 On 11/30/06, shelarcy [EMAIL PROTECTED] wrote:
 Hi Krasimir,

  On 11/30/06, shelarcy [EMAIL PROTECTED] wrote:
  But ... I can't install Visual Haskell prerelease 0.2. Near
  the end of install process, Microsoft Development Environment
  cause error.
 On Thu, 30 Nov 2006 17:03:22 +0900, Krasimir Angelov [EMAIL PROTECTED] 
 wrote:
  Could you tell me what error message you see during the installation?
  If it is in Japan then translate it in English ;-).

 It's not good error message. Anyway, I translate it.


Best Regards,

-- 
shelarcy shelarcycapella.freemail.ne.jp
http://page.freett.com/shelarcy/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: [Haskell] ANNOUNCE: Visual Haskell prerelease 0.2

2006-11-30 Thread shelarcy
Hi Krasimir,

 On 11/30/06, Krasimir Angelov [EMAIL PROTECTED] wrote:

 You can try to setup it manually using the following commands:

 $ regsvr32 /i:8.0 /n vs_haskell.dll
 $ regsvr32 /i:8.0 /n vs_haskell_babel.dll
 $ regsvr32 /i:8.0 /n vs_haskell_dlg.dll
 $ devenv.exe /Setup

Why you always show 8.0 instead of 7.1?


On Fri, 01 Dec 2006 03:48:49 +0900, Justin Bailey [EMAIL PROTECTED] wrote:
 I am having similar problems with the Visual Haskell install, and the
 commands given did not help. When I open Visual Studios Help | About dialog,
 I get an error about the package failing to initialize. I am installing to
 an English copy, however.

Their commands didn't help for my environment too.
I saw same error dialog that I sent previous mail.


 On 11/30/06, shelarcy [EMAIL PROTECTED] wrote:
  It's not good error message. Anyway, I translate it.
 
  Near the end of install process, error dialog opened and says:
 
  ---
  The problem happende, so exit Microsoft Development Environment.
  I'm sorry for causing inconvenience to you.
 
  (under its message, error dialog has form that send error report
  for Microsoft or shows error detail. These messages are not
  important, so I don't translate that.)
  ---
 
  And click form that shows error detail, another dialog opened.
  It shows:
 
  ---
  :Error ditail:
  An unhandled exception has been caught by the VSW exception filter.
  :Error Signature:
  AppName: devenv.exe  AppVer: 7.10.6030.0 ModName: unknown
  ModVer: 0.0.0.0  Offset: 00bbbacc
  :Report Detail:
  (Below meassage attetion to user that error report send what.
  So these messages are not important, too.)
  ---

Best Regards,

-- 
shelarcy shelarcycapella.freemail.ne.jp
http://page.freett.com/shelarcy/
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] How to get subset of a list?

2006-11-30 Thread Bernie Pope


On 01/12/2006, at 12:47 PM, Huazhi (Hank) Gong wrote:



Like given a string list s=This is the string I want to test, I  
want to get
the substring. In ruby or other language, it's simple like s 
[2..10], but how

to do it in Haskell?



If your indices are in ascending order, and unique, then something  
like this might

do the trick:

   els1 indexes list
  = els' (zip [0..] list) indexes
  where
  els' [] _ = []
  els' _ [] = []
  els' ((j,x):xs) indexes@(i:is)
 | i == j  = x : els' xs is
 | otherwise = els' xs indexes

Of course this is a right fold, so you ought to be able to use foldr.

Here's an attempt:

   els2 indexes list
  = foldr comb undefined [0..] list indexes
  where
  comb _ _ [] _ = []
  comb _ _ _ [] = []
  comb j rec (x:xs) indexes@(i:is)
 | j == i  = x : rec xs is
 | otherwise = rec xs indexes

Bonus marks for figuring out why I used undefined.

Warning: this is largely untested code.

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


[Haskell-cafe] Re: How to get subset of a list?

2006-11-30 Thread oleg

Huazhi (Hank) Gong wrote:

 Like given a string list s=This is the string I want to test, I want to get
 the substring. In ruby or other language, it's simple like s[2..10], but how
 to do it in Haskell?

Quite simply, actually:

 infixl 1 %%
 str %% idxs = map (str !!) idxs

That is it. Not the most efficient, but gets the job done.

 tstring = This is the string I want to test
 test1 = tstring %% [2..10]

*Sub test1
is is the

 However, like I want to choose s[1,3,6,10] or something like this.
 Are there some straightforward function or operator for doing this
 job?

Yes, see above.

 test2 = tstring %% [1,3,6,10]

*Sub test2
hsse

Indices don't have to be in the increasing order

 test3 = tstring %% [10,6,3,1]

*Sub test3
essh

or in any order...

 test4 = tstring %% [10,6,3,1]++[2..10]

*Sub test4
esshis is the

Of course if one cares about the overhead of running code (rather than
the overhead of writing code), one would probably ask, as several
posters did, if the list of characters is the right data structure and
if the problem indeed calls for random access to the elements of the
list.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Draft MissingH Reorg Plan

2006-11-30 Thread John Goerzen
Please tell me if I should just go away or go to another list here.

Thanks again for all the feedback you've sent.

I've got the new MissingH website getting started, and I've posted there
the draft reorganization, module rename, and package split plan here:

  http://software.complete.org/missingh/wiki/TransitionPlanning

Your comments (and edits! -- must register/login first) are welcome.

I have not yet audited the plan for dependency sanity.  This could
complicate things a few places, but hopefully not too many.

-- John

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


Re: [Haskell-cafe] Draft MissingH Reorg Plan

2006-11-30 Thread Tomasz Zielonka
On Fri, Dec 01, 2006 at 04:06:08AM +, John Goerzen wrote:
 I've got the new MissingH website getting started, and I've posted there
 the draft reorganization, module rename, and package split plan here:
 
   http://software.complete.org/missingh/wiki/TransitionPlanning
 
 Your comments (and edits! -- must register/login first) are welcome.

Do you accept contributions? I have some code I find very useful that
would fit in the same places, like in Text.ParserCombinators.Parsec.Utils,
Data.BitsUtils (btw, why not Data.Bits.Utils?), Control.Concurrent.*.

As for other code (say Data.Tree.Utils), I am not sure what's best: put
it in some big library like yours, or publish as separate small
libraries. There is more work with the latter, but it seems more clean,
and easy to review for the user.

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


[Haskell-cafe] Beginner: IORef constructor?

2006-11-30 Thread TJ

First of all, sorry if this is a really silly question, but I couldn't
figure it out from experimenting in GHCi and from the GHC libraries
documentation (or Google).

Is there an IORef consturctor? Or is it just internal to the Data.IORef module?

I want a global variable, so I did the following:

--
module VirtualWorld where
 import Data.IORef
 theWorld = IORef [] -- This will be writeIORef'ed with a populated
list as the user modifies the world.
-

It doesn't work. GHCi says that the IORef constructor is not in scope.
I did a :module Data.IORef and then IORef [] and it still gives me
the same error.

I'm using GHC 6.6 on Windows.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Beginner: IORef constructor?

2006-11-30 Thread Bernie Pope


On 01/12/2006, at 6:08 PM, TJ wrote:


First of all, sorry if this is a really silly question, but I couldn't
figure it out from experimenting in GHCi and from the GHC libraries
documentation (or Google).

Is there an IORef consturctor? Or is it just internal to the  
Data.IORef module?


I want a global variable, so I did the following:

--
module VirtualWorld where
 import Data.IORef
 theWorld = IORef [] -- This will be writeIORef'ed with a populated
list as the user modifies the world.
-

It doesn't work. GHCi says that the IORef constructor is not in scope.
I did a :module Data.IORef and then IORef [] and it still gives me
the same error.

I'm using GHC 6.6 on Windows.


Hi TJ,

IORef is an abstract data type, so you cannot refer to its  
constructors directly.


Instead you must use:

   newIORef :: a - IO (IORef a)

which will create an IORef on your behalf. Note that the result is in  
the IO type,

which limits what you can do with it.

If you want a global variable then you can use something like:

   import System.IO.Unsafe (unsafePerformIO)

   global = unsafePerformIO (newIORef [])

But this is often regarded as bad programming style (depends who you  
talk to). So you
should probably avoid this unless it is really necessary (perhaps you  
could use a state

monad instead?)

Read the comments about unsafePerformIO on this page:

   http://www.haskell.org/ghc/docs/latest/html/libraries/base/System- 
IO-Unsafe.html


especially the notes about NOINLINE and -fno-cse

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


Re: [Haskell-cafe] Re: [Haskell] ANNOUNCE: Visual Haskell prerelease 0.2

2006-11-30 Thread Krasimir Angelov

Hi Shelarcy,

On 12/1/06, shelarcy [EMAIL PROTECTED] wrote:

Why you always show 8.0 instead of 7.1?


Sorry, I thought that you are using VStudio 2005.


On Fri, 01 Dec 2006 03:48:49 +0900, Justin Bailey [EMAIL PROTECTED] wrote:
 I am having similar problems with the Visual Haskell install, and the
 commands given did not help. When I open Visual Studios Help | About dialog,
 I get an error about the package failing to initialize. I am installing to
 an English copy, however.

Their commands didn't help for my environment too.
I saw same error dialog that I sent previous mail.


I saw this message this morning:

http://www.cygwin.com/ml/cygwin/1998-04/msg00133.html

I wonder whether this may cause the problem. I have uploaded a new
vs_haskell.dll here:

http://www.haskell.org/visualhaskell/vs_haskell.zip

It is the same dll but without stripped debug symbols. Could you try
to replace it in your installation?

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


Re: [Haskell-cafe] Draft MissingH Reorg Plan

2006-11-30 Thread Taral

On 12/1/06, Tomasz Zielonka [EMAIL PROTECTED] wrote:

Do you accept contributions? I have some code I find very useful that
would fit in the same places, like in Text.ParserCombinators.Parsec.Utils,
Data.BitsUtils (btw, why not Data.Bits.Utils?), Control.Concurrent.*.


Hey, contributions. I'll throw in my haskell MIME parser if you want
it. It's not the same as the one that most people use -- but I like it
better. :)

--
Taral [EMAIL PROTECTED]
You can't prove anything.
   -- Gödel's Incompetence Theorem
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe