Re: [Haskell-cafe] develop new Haskell shell?

2006-05-16 Thread John Hamilton

Jared Updike wrote:

It would also be wise to look at occam and erlang and see if they have
any useful ideas. And, of course, Windows PowerShell.


And scsh (Scheme shell, pretty full featured these days):  
http://www.scsh.net/


At

http://jaortega.wordpress.com/2006/05/16/not-your-parents-shell/

there is an interesting blog post about scsh and a new frontend for it 
called Commander S.

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


[Haskell-cafe] Controlling scope using monadic classes

2006-05-16 Thread Daniel McAllansmith
Hi.

I'm trying to control the scope within which functions can be used by putting 
them in a type class.
Unfortunately I can't seem to figure out how to get it done.  Any advice would 
be much appreciated.

What I want is to start out in a certain scope, which restricts me to using 
functions in that scope or opening up a subsidiary scope at which point I'm 
restricted to functions in that scope or opening up an even deeper scope.

Hopefully a failed attempt will help explain what I'm trying to achieve... the 
following has trouble with the inScope{B,C} functions.

type AInfo = String
type BInfo = String
type CInfo = String

type BResult = Int
type CResult = Char

class (Monad m) => WithinA m where
askAInfo :: m AInfo

class (WithinA m) => WithinB m where
askBInfo :: m BInfo

class (WithinB m) => WithinC m where
askCInfo :: m CInfo

class (WithinA m) => ScopeA m where
getAInfo:: m AInfo
putAInfo:: AInfo -> m ()
updateAInfo :: BResult -> m ()
inScopeB:: (ScopeB m2) => m2 BResult -> m BResult

class (WithinB m) => ScopeB m where
getBInfo :: m BInfo
putBInfo :: BInfo -> m ()
inScopeC :: (ScopeC m2) => m2 CResult -> m CResult

class (WithinC m) => ScopeC m where
getCInfo :: m CInfo
putCInfo :: CInfo -> m ()

aScoped :: (ScopeA m) => m String
aScoped = do
bResult <- inScopeB bScoped
updateAInfo bResult
return "done"

bScoped :: (ScopeB m) => m BResult
bScoped = do
i1 <- b1
i2 <- b2
return (i1 + i2)

b1 :: (ScopeB m) => m Int
b1 = return 2

b2 :: (ScopeB m) => m Int
b2 = inScopeC cScoped >>= return . fromEnum

cScoped :: (ScopeC m) => m Char
cScoped = return '('


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


Re: [Haskell-cafe] GNUPlot (Was: Troubles with FFI)

2006-05-16 Thread SevenThunders

Thanks for the gnuplot stuff.  I intend to try that out.  Perhaps sooner than
later.
As for lhs2tex, since no windows installer is provided, it might be a bit
trickier and my time
is very limited. Also after reviewing the manual it seems to still be
focused on literate programming more than active documents.  Active document
support in general seems to be hard to find in the open source world.  I
have Maple, but their new document mode is not very useful for producing
quality typeset mathematics and figures. 

My best results have been using either programmatically generated latex
macros for inclusion into a document, or to use search and replace on text
based document formats (e.g. .rtf or I suppose .pdf)
--
View this message in context: 
http://www.nabble.com/Troubles-with-FFI-t1611744.html#a4421523
Sent from the Haskell - Haskell-Cafe forum at Nabble.com.

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


Re: [Haskell-cafe] RE: Troubles with FFI

2006-05-16 Thread wld

[Seven, sorry for replying just to you. Now mailing and posting]
On 5/17/06, SevenThunders <[EMAIL PROTECTED]> wrote:


Thats some good info.  It probably should go on that wiki page.
All I need now is an unlimited amount of spare time...
--
View this message in context: 
http://www.nabble.com/Troubles-with-FFI-t1611744.html#a4420914
Sent from the Haskell - Haskell-Cafe forum at Nabble.com.

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


Please quote some part of the messages you replay to. I think you
use some web-interface so you see what previous messages. Most
list subscribers just get the text quoted above. What is this "good info"?
I don't know. I (an most of others) will not bother to "view this message in
context..." This is a mailing list, NOT a forum.

Regards,


--
V.Rudenko
--
λ is the ultimate
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] RE: Troubles with FFI

2006-05-16 Thread SevenThunders

Thats some good info.  It probably should go on that wiki page.
All I need now is an unlimited amount of spare time...
--
View this message in context: 
http://www.nabble.com/Troubles-with-FFI-t1611744.html#a4420914
Sent from the Haskell - Haskell-Cafe forum at Nabble.com.

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


[Haskell-cafe] RE: RE: Troubles with FFI

2006-05-16 Thread SevenThunders

Aarrgh! Are the formatting commands the same?

I don't want to have to rewrite the whole thing.

That is a bit confusing.
--
View this message in context: 
http://www.nabble.com/Troubles-with-FFI-t1611744.html#a4420902
Sent from the Haskell - Haskell-Cafe forum at Nabble.com.

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


[Haskell-cafe] Haskell DB and XML libs: one user's experience

2006-05-16 Thread Robert Dockins

Hello all,


I recently found myself needing to do some data manipulation; I  
needed to take some data from a database and generate a series of XML  
files from it.  In the past I've done most of this sort of work in  
Java, but this time I decided I'd take the opportunity to explore the  
state of the art of Haskell DB and XML libraries.



As to DB, I tried using HDBC first.  I was actually a little  
surprised how straightforward it was.  My database (PostgreSQL) is  
directly supported, and the compile/install went smoothly.  My first  
test connection program that typechecked worked as expected (!) and I  
was soon executing queries doing useful work with the results.  I'd  
just like to take a moment to congratulate John Goerzen for creating  
a product with a low barrier of entry for using databases in  
Haskell.  As I didn't really do anything beyond simple queries, can't  
comment on more advanced features.



For XML, I wavered between HaXml and HXT (the Haskell XML Tookbox).   
I initially decided to use HXT because it has support for xml  
namespaces, which I was going to need, and because it just seems to  
be the most complete and advanced package available.  The HXT install  
suffers a little bit from transitive-closureitis, but, overall wasn't  
too bad.  However, I had a really hard time using it!  The API is  
_really_ intimidating, and I couldn't find any basic tutorial-style  
documentation.  The API docs are a little hard to use because related  
definitions are spread out over a bunch of modules, and the links  
don't always work.  Also, the theses are nice, but they read like  
theses ;-)  That's not what I want when I have a job to complete.   
Long story made short; I couldn't figure out how to create and XML  
document and serialize it to disk.  I was reasonably motivated and  
I'm a pretty experienced Haskell programmer, but I had to call it  
quits after about 3 hours of struggling with it.  Most of my programs  
would mysteriously fail to produce output OR errors!  It was really  
frustrating.



I ended up using HaXml instead and shoehorning in the namespaces by  
using attributes named "xmlns:xyz" etc. on the document root element  
(which is OK, but not ideal).  The HaXml API was also tough to work  
with but was less mystifying than HXT's, and I eventually got it to  
work.  I was a little disappointed by the results, because the pretty  
printer does some fairly bizarre things to ensure that it doesn't  
introduce extra whitespace into the DOM.  I also had to do some  
futzing to make HaXml correctly escape literal text.  Finally, the  
using the HaXml API to generate XML results in verbose code that's  
hard to read.  I was hoping that I'd get results comparable to using  
xmlenc (http://xmlenc.sourceforge.net/) in Java, but I was  
disappointed by fairly low signal-to-noise ratio (although in all  
fairness, its probably comparable to using the DOM or SAX Java  
APIs).  Overall, HaXml works, but feels a bit awkward, at least for  
this use case.



Now taking a slightly closer look at HXML, I see that it may be the  
best choice for what I was attempting to do (although it also doesn't  
support namespaces).  The simplified representation looks  
particularly nice for building XML from scratch.  I may try rewriting  
with HXML and see how that goes.



So that's it.  I don't have any deep conclusions, but I thought I'd  
share my experiences in the hopes that they will be helpful to somebody.




Rob Dockins

Speak softly and drive a Sherman tank.
Laugh hard; it's a long way to the bank.
  -- TMBG

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


RE: [Haskell-cafe] RE: Troubles with FFI

2006-05-16 Thread Simon Peyton-Jones
A confusing thing is that the Haskell web site is primarily now using
MedaWiki
http://haskell.org/haskellwiki/Haskell
It used to use MoinMoin (pages starting http://www.haskell.org/hawiki),
and that's what you used.  I think your new input will be more
long-lasting if you use the former.  We're trying to move stuff from the
latter to the former.

simon

| -Original Message-
| From: [EMAIL PROTECTED]
[mailto:[EMAIL PROTECTED] On Behalf Of
| SevenThunders
| Sent: 16 May 2006 04:14
| To: haskell-cafe@haskell.org
| Subject: [Haskell-cafe] RE: Troubles with FFI
| 
| 
| Done!  Thanks for the tip.
| I added a wiki page on this with my overly simple examples.
| Perhaps I'll extend it as I learn more.
| 
| http://www.haskell.org/hawiki/FfiWithArrays
| --
| View this message in context:
http://www.nabble.com/Troubles-with-FFI-t1611744.html#a4402742
| Sent from the Haskell - Haskell-Cafe forum at Nabble.com.
| 
| ___
| Haskell-Cafe mailing list
| Haskell-Cafe@haskell.org
| http://www.haskell.org/mailman/listinfo/haskell-cafe
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] RE: Troubles with FFI

2006-05-16 Thread Brian Hulley

SevenThunders wrote:

Done!  Thanks for the tip.
I added a wiki page on this with my overly simple examples.
Perhaps I'll extend it as I learn more.

http://www.haskell.org/hawiki/FfiWithArrays


[From section under matrix1.hs example]


Now as a Haskell newbie I've been informed that the input array
that is the second argument of sumarr, should be wrapped in
an IO monad to keep all access sequential.


No - everything is fine as you've got it at the moment. All access is 
already sequential because the result of your C function is an IO action 
rather than a pure value ie IO CDouble instead of CDouble



Doing so, however, breaks this code so that it won't compile.
It seems to me that the withStorableArray access function will only
return a pointer to the elements that is already wrapped in a monad.


afaiu withStorableArray just returns an IO action, which, when executed, 
will supply the function with the pointer it needs. The result of the IO 
action (the value contained inside the monadic value of type "IO CDouble") 
is the result of the function (in your case a CDouble)


Shouldn't this already guarantee unique (sequential) access to the 
pointer?
Yes, because IO actions can only be *executed* in sequence even though they 
can be *created* in any old place (assuming you don't use forkIO etc but 
that's a different story altogether)



However, what is disturbing about this is what happens if we need
to replicate the pointer argument over multiple arguments in C
(or some other language).


This should be fine as long as the Ptr passed to the C function is not 
allowed to escape from the nesting given by withStorableArray - it is only 
valid while the IO action returned by withStorableArray is executing, 
because this is the only point at which the garbage collector is not allowed 
to move the array about.



Also the business of having to pass
multiple mutable arrays into one C function call should be
addressed. For now that remains a TBD in this tutorial.


void multarr(double *mat1Raw, double *mat2Raw, double *resultRaw){
// multiply mat1 by mat2 and store in result matrix
// You could mutate all of the matrices here but for multiplication 
obviously only

// the result needs to be mutated
}

foreign import ccall multarr :: Ptr Double -> Ptr Double -> Ptr Double -> IO 
()


main = do
  mat1 <- newListArray ...
  mat2 <- newListArray ...
  result <- newListArray ...
  withStorableArray mat1 (\mat1Raw ->
   withStorableArray mat2 (\mat2Raw ->
 withStorableArray result (multarr mat1Raw 
mat2Raw)))


The nested calls to withStorableArray can be avoided by defining your own 
helper functions eg:


withStorableArray3
 ::  StorableArray i1 e1
-> StorableArray i2 e2
-> StorableArray i3 e3
-> (Ptr e1 -> Ptr e2 -> Ptr e3 -> IO a)
-> IO a
withStorableArray3 a1 a2 a3 f =
   withStorableArray a1 (\a1Raw ->
  withStorableArray a2 (\a2Raw ->
   withStorableArray a3 (f a1Raw a2Raw)))

Regards, Brian.

PS: In GHC it's better to use the command line option (or option pragma in 
the source module) -#include "matrix_c.h" because if you put the header in 
the import declaration in GHC you lose inlining optimizations. 


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


[Haskell-cafe] transactional cache

2006-05-16 Thread Alberto G. Corona

Finally i did it. The transactional cache uses STM, no blocking MVars.

I created has a simple interface, the transactional "plumbing" is
hidden in the TransactCacheSTM module.  The usage is simple:

withResources [object1, object2,..] process
 where
process[maybeObject1,maybeObject2.]= [newObject1,newObect2...]
newObject1=.
newObject2=

"process" run atomically, object1,object2.. are partially defined,
just with the fields neccesary to retrieve them. newObjects are the
resulting objects that replace the previous content in the cache. Non
existing objects are created.

the objects must implement "IResource" type class procedures for
reading, writing and obtaining a unique key so that the objects can be
read to, write from and do search from the cache. No other asumptions
are made about the object types or storages.

In the following example, client Alberto buy a computer. the total
amount due by Alberto is increased with the computer price. The
quantity of the item "computer" in stock is decreased.

withResources[Client{name="Alberto"}, Item{iname="computer"} buy
 where
 buy[Nothing,_]= error "Client does not exist"
 buy[_,Nothing]= error "Item does not exist"
 buy[Just client, Just item]= [client{total client=total client+
price item},
  item{quantity=quantity-1}]


The resulting code is transactional and clean. The  object is read if
not already in the cache using the user defined procedure for that
object (either a sql query or read from a file).

The write is delayed depending on object usage in the cache and the
cache size. I also defined ordinary, non transactional object
retrieval (getResources :: [Resource]->IO[Resource]  )

To have real ACID transactions, I also defined a procedure for atomic
write of the entire cache to disk, in order to have  coherent content
in permanent storage,

(I´m using it on a portal 100% coded in Haskell (I love Haskell since
i knew it five months ago).  this trhansactional cache makes the data
handling in my portal a lot easier. I use XML files, no boring
database tables are necessary.

I will put online the transactional cache sometime later, but by now I
will send te code by mail to anyone interested.


Message: 8
Date: Sat, 13 May 2006 12:26:42 +0900
From: "Evan Martin" <[EMAIL PROTECTED]>
Subject: Re: [Haskell-cafe] RE: transactional cache
To: "Alberto G. Corona" <[EMAIL PROTECTED]>
Cc: haskell-cafe@haskell.org
Message-ID:
  <[EMAIL PROTECTED]>
Content-Type: text/plain; charset=ISO-8859-1; format=flowed

On 5/13/06, Alberto G. Corona <[EMAIL PROTECTED]> wrote:

> notglobal = newIORef True
> main = do a <- notglobal
> b <- notglobal

Thanks. I got the poit more or less; Each invocation creates a new
IORef instance.


Another way of looking at this, that might be more instructive, is
that notglobal is defined to be the action of creating a new IO ref.
You can see that in its type:
> :t newIORef True
newIORef True :: IO (IORef Bool)
I read that type as "an IO operation that produces an IORef Bool when executed".

Then the code in main "executes" notglobal twice.

Another way of looking at this is that you can always substitute the
right side of an equals sign in for the left side.  If you do that on
this code this makes it plain that a and b will be different.
(unsafePerformIO breaks this substitution rule.)
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] GNUPlot (Was: Troubles with FFI)

2006-05-16 Thread Donald Bruce Stewart
lemming:
> 
> On Mon, 15 May 2006, SevenThunders wrote:
> 
> > I'd consider linux, but I don't have linux licenses for Matlab or Maple and
> > I have to interface to the corporate MS world.  Thus my 'solution'  will be
> > to make a very light weight matrix class that only pulls in a few BLAS and
> > Lapack routines coupled with a few file based routines with gnuplot as the
> > output, or perhaps pathon _ gnuplot as the output.  With any luck I'll be
> > able to open source that, if it does anybody any good.
> 
> I have a wrapper for basic GNUPlot control:
>  http://www.math.uni-bremen.de/~thielema/Research/GNUPlot.hs

More secret modules! Could you stick a link to this on the haskell.org
wiki please, under libraries and tools somewhere?

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


[Haskell-cafe] GNUPlot (Was: Troubles with FFI)

2006-05-16 Thread Henning Thielemann

On Mon, 15 May 2006, SevenThunders wrote:

> I'd consider linux, but I don't have linux licenses for Matlab or Maple and
> I have to interface to the corporate MS world.  Thus my 'solution'  will be
> to make a very light weight matrix class that only pulls in a few BLAS and
> Lapack routines coupled with a few file based routines with gnuplot as the
> output, or perhaps pathon _ gnuplot as the output.  With any luck I'll be
> able to open source that, if it does anybody any good.

I have a wrapper for basic GNUPlot control:
 http://www.math.uni-bremen.de/~thielema/Research/GNUPlot.hs

> After that I need to automate document creation from the output of math
> simulations.  I'll use Latex as the engine for that.  It's something I've
> done before to great effect.

lhs2TeX can be of help for starting Haskell computations and integrating
the results into the document.

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