Re: [Haskell-cafe] pure Haskell database

2008-09-25 Thread Rich Neswold
On Thu, Sep 25, 2008 at 11:09 AM, Manlio Perillo
[EMAIL PROTECTED]wrote:

 Rich Neswold ha scritto:

 On Wed, Sep 24, 2008 at 4:17 PM, Manlio Perillo [EMAIL PROTECTED]mailto:
 [EMAIL PROTECTED] wrote:

I need a simple, concurrent safe, database, written in Haskell.
A database with the interface of Data.Map would be great, since what
I need to to is atomically increment some integer values, and I
would like to avoid to use SQLite.

 How about  MVar (Map k Int)?  or even Map k (MVar Int)?


 Yes, it is a solution; and I can run a thread that every N seconds writes
 the database to a file.

 But this works only if the database is used by only one process.


Ah. When you said concurrent safe, I thought you meant within the
application. You're looking for something like
thishttp://hackage.haskell.org/cgi-bin/hackage-scripts/package/anydbm
.

-- 
Rich

LOI: https://www.google.com/reader/shared/00900594587109808626
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] pure Haskell database

2008-09-24 Thread Rich Neswold
On Wed, Sep 24, 2008 at 4:17 PM, Manlio Perillo [EMAIL PROTECTED]wrote:

 I need a simple, concurrent safe, database, written in Haskell.
 A database with the interface of Data.Map would be great, since what I need
 to to is atomically increment some integer values, and I would like to avoid
 to use SQLite.


How about  MVar (Map k Int)?  or even Map k (MVar Int)?

-- 
Rich

LOI: https://www.google.com/reader/shared/00900594587109808626
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] MonadPlus

2008-05-09 Thread Rich Neswold
On Fri, May 9, 2008 at 2:39 PM, Andrew Coppin [EMAIL PROTECTED]
wrote:

 [In a somewhat unrelated question... I saw some code the other day that
 used Either as if it were a monad. And yet, I don't see an instance given in
 the standard libraries - even though there should be one. I can see Functor
 (Either a), but not Monad (Either a) or even Monad (Either String)...]


It's used in the Error Monad.

-- 
Rich

JID: [EMAIL PROTECTED]
LOI: https://www.google.com/reader/shared/00900594587109808626
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Help using CGIT

2007-08-24 Thread Rich Neswold
On 8/24/07, Bjorn Bringert [EMAIL PROTECTED] wrote:

 On Aug 23, 2007, at 3:34 , Rich Neswold wrote:

  Bingo! Method #3 works beautifully! I missed the using-lift-with-
  the-constructor permutation.
 
  Thanks for your help!

 I started writing a tutorial for Haskell web programming with the cgi
 package a while back, but haven't worked on it for a while, see
 http://www.haskell.org/haskellwiki/Practical_web_programming_in_Haskell
 I haven't added it to the list of tutorials yet, since it's still
 rather incomplete.

 The section on using CGIT is just a stub, perhaps you would like to
 contribute to it? See
 http://www.haskell.org/haskellwiki/
 Practical_web_programming_in_Haskell#Extending_the_CGI_monad_with_monad_
 transformers


Done. As I learn more about using CGIT, I'll try to remember to add more
content. Any suggestions to improve it are welcome!

-- 
Rich

JID: [EMAIL PROTECTED]
AIM: rnezzy
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Help using CGIT

2007-08-22 Thread Rich Neswold
Hello!

I've been having a tough time trying to use the CGI monad transformer
(CGIT). Hopefully someone can show me my misstep(s).

I have a CGI script that's evolving. Early on, it needed a single
database access. Now it's doing two accesses (and it looks like I'll
be adding more.) Rather than making a connection for each access, the
script needs to connect once. To do this, I want to combine the CGI
monad with the Reader monad.

This version compiles cleanly:

 module AppMonad (App (..), runApp)
 where

 import Control.Exception (bracket)
 import Control.Monad.Reader
 import Network.CGI.Monad
 import Network.CGI.Protocol
 import System.IO (stdin, stdout)
 import Database.HSQL.PostgreSQL

 newtype App a = App (ReaderT Connection (CGIT IO) a)
deriving (Monad, MonadIO, MonadReader Connection)

 runApp :: App CGIResult - IO ()
 runApp (App a) =
 bracket (connect host dbname user password)
 disconnect
 (\c - do { env - getCGIVars
   ; hRunCGI env stdin stdout (runCGIT (runReaderT a c))
   ; return () } )

Unfortunately, when another module tries to actually use the monad, I
get warnings about No instance for (MonadCGI App). I tried making an
instance:

 instance MonadCGI App where
 cgiAddHeader = ?
 cgiGet = ?

But I don't know how to define these functions. I tried various
'lift'ing combinations, but couldn't come up with a solution that
would compile. I'm also disappointed that I had to break apart
'runCGI' (by cut-and-pasting its source) because I couldn't make it
believe my monad looked enough like MonadCGI.

My previous experiment with monad transformers was successful. It
didn't use CGIT, however, so the 'run*' functions were simpler.

Does anyone have an example of using CGIT (I didn't find any from
Google)? Shouldn't I be able to use 'runCGI' with my monad? CGIT users
shouldn't be required to re-implement 'runCGI, right?

Any help or ideas is appreciated!

-- 
Rich

JID: [EMAIL PROTECTED]
AIM: rnezzy
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Help using CGIT

2007-08-22 Thread Rich Neswold
On 8/22/07, Ian Lynagh [EMAIL PROTECTED] wrote:

 On Wed, Aug 22, 2007 at 01:27:00PM -0500, Rich Neswold wrote:
 
   newtype App a = App (ReaderT Connection (CGIT IO) a)
  deriving (Monad, MonadIO, MonadReader Connection)
 
  Unfortunately, when another module tries to actually use the monad, I
  get warnings about No instance for (MonadCGI App). I tried making an
  instance:
 
   instance MonadCGI App where
   cgiAddHeader = ?
   cgiGet = ?

 You have three choices:

 1:

 2:

 3:
 Provide a single instance for App that does the whole thing:
 instance MonadCGI App where
 cgiAddHeader n v = App $ lift $ cgiAddHeader n v
 cgiGet x = App $ lift $ cgiGet x
 This one you would obviously have to change if you added a StateT.


Bingo! Method #3 works beautifully! I missed the
using-lift-with-the-constructor permutation.

Thanks for your help!

-- 
Rich

JID: [EMAIL PROTECTED]
AIM: rnezzy
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Re: Bi-directional Maps

2007-08-20 Thread Rich Neswold
On 8/20/07, apfelmus [EMAIL PROTECTED] wrote:

 Andrew Wagner wrote:
  It occurred to me that it would be useful to explicitly
  have a Bi-directional Map, which does the maintenance of keeping the
  Maps synchronized behind the scenes. Thus, Bimap was born!

 ... most of the map functions (including  update  above) probably won't
 work anyway, what should

left_insertWith (\new old - new) 'a' 1 (fromList [('a',2),('b',1)])

 do? I can't yield

fromList [('a',1),('b',1)]

 since 1 has two keys now.


Exactly. For this to work there needs to be the constraint that there's a
one-to-one mapping in each direction. The Bimap should have the uniqueness
promise that Set (k, v) gives. Yet you should be able to search on either
tuple value.

-- 
Rich

JID: [EMAIL PROTECTED]
AIM: rnezzy
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] interrupting an accept()ing thread

2007-07-07 Thread Rich Neswold

On 7/7/07, Lukas Mai [EMAIL PROTECTED] wrote:


If I understand this correctly, spin should be written as:

spin = do
block $ do
(t, _) - accept s
unblock (forkIO $ doStuff t) `finally` sClose t
spin



I think the `finally` portion should be done in the forked process context.
Otherwise once the process is forked, the socket gets closed by the parent
process. Something more along the lines of:

unblock (forkIO $ doStuff t `finally` sClose t)

--
Rich

JID: [EMAIL PROTECTED]
AIM: rnezzy
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] interrupting an accept()ing thread

2007-07-06 Thread Rich Neswold

On 7/5/07, Lukas Mai [EMAIL PROTECTED] wrote:


Hello, cafe!

I have the following code (paraphrased):

...
forkIO spin
...
spin = do
(t, _) - accept s   -- (*)
forkIO $ dealWith t  -- (**)
spin

My problem is that I want to stop spin from another thread. The obvious
solution would be to throw it an exception. However, that leaks a socket
(t) if the exception arrives between (*) and (**). I could wrap the whole
thing in block, but from looking at the source of Network.Socket it seems
that accept itself is not exception safe; so no matter what I do, I can't
use asynchronous exceptions to make spin exit.



What about using bracketOnError?

nextClient s = bracketOnError (fst . accept s) sClose

spin = do
   nextClient s (\s' - forkIO $ dealWith s')
   spin

If bracketOnError leaks the resource in the event of an exception, then it
needs to be fixed.

--
Rich

JID: [EMAIL PROTECTED]
AIM: rnezzy
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Telling the time

2007-06-21 Thread Rich Neswold

On 6/21/07, Andrew Coppin [EMAIL PROTECTED] wrote:


Is there a standard library function anywhere which will parse a string
into some kind of date/time representation?



In Data.Time.Format, there's parseTime. parseTime takes a format string that
describes the layout. Since you have varying layouts in your files
(hopefully consistent in the same file!), you simply change the format
string for each file.

--
Rich

JID: [EMAIL PROTECTED]
AIM: rnezzy
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] [IO Int] - IO [Int]

2007-05-04 Thread Rich Neswold

On 5/4/07, Phlex [EMAIL PROTECTED] wrote:


Hello all,

I'm trying to learn haskell, so here's is my first newbie question.
I hope this list is appropriate for such help requests.

I'm trying to write a function with the signature [IO Int] - IO [Int]



Control.Monad has a function (called sequence) that does this for you. In
fact, sequence is a more generic solution since its signature is
(Monadhttp://haskell.org/ghc/docs/latest/html/libraries/base/Control-Monad.html#t%3AMonadm
= [m a] - m [a]).

As a newbie, I found it educational to peruse the various modules in 
http://haskell.org/ghc/docs/latest/html/libraries/;. Just start looking at
modules that sound interesting and see what has already been defined. Some
modules at first may be too advanced, but if you go back to them in a few
days (weeks?), they'll start making more sense, too.

--
Rich

AIM : rnezzy
ICQ : 174908475
Jabber: [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: Re[2]: [Haskell-cafe] Tracking characters and a timestamp ?

2007-04-05 Thread Rich Neswold

On 4/5/07, Bulat Ziganshin [EMAIL PROTECTED] wrote:

you definitely should read http://haskell.org/haskellwiki/IO_inside


Thanks for mentioning this link -- I wasn't aware of it. I wish it
existed when I first started learning Haskell...

--
Rich

AIM : rnezzy
ICQ : 174908475
Jabber: [EMAIL PROTECTED]
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] split string into n parts

2006-10-23 Thread Rich Neswold
On 10/23/06, jim burton [EMAIL PROTECTED] wrote:  I want to split a string into 5 parts of equal length, with the last fifth padded if necessary, but can't get it right
I got this:fifths :: String - Stringfifths xs = let len = (length xs + 4) `div` 5 padded = take (len * 5) (xs ++  ) in unwords $ nth len padded
 where nth _ [] = [] nth n xs = (take n xs) : (nth n $ drop n xs) *Main fifths IDOLIKETOBEBESIDETHESEASIDE IDOLI KETOBE BESIDE THESEA SIDEXX *Main fifths 12345
 1 23 45This gives the following results:IDOLIK ETOBEB ESIDET HESEAS IDE and1 2 3 4 5But it also gives this result, which may or may not be correct for your problem:
*Main fifths 12345612 34 56 -- RichAIM : rnezzyICQ : 174908475
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Receiving multicasts

2006-06-15 Thread Rich Neswold

Hello,

Has anyone figured out a way to receive multicasts in a Haskell
program? It doesn't appear that Network.Socket.setSocketOption
provides enough information to join a multicast address.

Any information would be appreciated.

--
Rich

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


[Haskell-cafe] Constructor constraints

2005-09-20 Thread Rich Neswold
Hello,I've looked through the two tutorials and the Report, but couldn't find help on this topic. My question is whether you can place constraints on new data types. For instance, I want to make a new type that is a 4 element tuple where each element is greater than or equal to the previous entry. Is this possible?
i.e.data Category = Membership a a a aI'd like to be able to prevent invalid Category data from being created. Any information would be appreciated.
-- RichAIM : rnezzyICQ : 174908475
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


Re: [Haskell-cafe] Constructor constraints

2005-09-20 Thread Rich Neswold
On 9/20/05, Malcolm Wallace [EMAIL PROTECTED] wrote:
You can make a 'smart' constructor function, and hide the real dataconstructor so that it cannot be used:Thanks! I'll give your solution a try.-- RichAIM : rnezzy
ICQ : 174908475
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe