Re: [Haskell-cafe] TLS support for haskell-xmpp

2012-04-20 Thread John Goerzen

I'll probably give it a go then.

Incidentally, I am not sure if the original author is responsive.  I'm 
fixing some other bugs while I'm at it; would it be kosher for me to 
make a new version upload of it to Hackage in the event that the 
original author doesn't respond?


-- John

On 04/17/2012 04:31 AM, Vincent Hanquez wrote:

On 04/17/2012 04:05 AM, John Goerzen wrote:

Dmitry  others,

Attached is a diff implementing TLS support for haskell-xmpp, and 
correcting a build failure.


The support is rough but it seems to work so far.


It's a bid sad but gnutls is GPL-3 and haskell-xmpp BSD3, rendering 
the combination BSDless.
May i suggest in a shameless self advertising, the haskell tls library 
:-)




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


[Haskell-cafe] TLS support for haskell-xmpp

2012-04-16 Thread John Goerzen

Dmitry  others,

Attached is a diff implementing TLS support for haskell-xmpp, and 
correcting a build failure.


The support is rough but it seems to work so far.

-- John
diff -durN -x '*~' -x Test.hs orig/haskell-xmpp-1.0/haskell-xmpp.cabal haskell-xmpp-1.0/haskell-xmpp.cabal
--- orig/haskell-xmpp-1.0/haskell-xmpp.cabal	2011-01-15 16:50:14.0 -0600
+++ haskell-xmpp-1.0/haskell-xmpp.cabal	2012-04-16 21:03:49.125224872 -0500
@@ -32,7 +32,7 @@
 
 library
   Hs-Source-Dirs: ./src
-  Build-Depends: base  3  =5, random, pretty, array, HaXml = 1.20.2, mtl = 1.0, network, html, polyparse, regex-compat, stm, utf8-string
+  Build-Depends: base  3  =5, random, pretty, array, HaXml = 1.20.2   1.21, mtl = 1.0, network, html, polyparse, regex-compat, stm, utf8-string, gnutls, bytestring
   Exposed-modules: Network.XMPP
 , Network.XMPP.Sasl
 , Network.XMPP.Core
diff -durN -x '*~' -x Test.hs orig/haskell-xmpp-1.0/src/Network/XMPP/Concurrent.hs haskell-xmpp-1.0/src/Network/XMPP/Concurrent.hs
--- orig/haskell-xmpp-1.0/src/Network/XMPP/Concurrent.hs	2011-01-15 16:50:14.0 -0600
+++ haskell-xmpp-1.0/src/Network/XMPP/Concurrent.hs	2012-04-16 21:46:04.405285127 -0500
@@ -36,6 +36,8 @@
 import Network.XMPP.XEP.Version 
 import Network.XMPP.IM.Presence
 import Network.XMPP.Utils
+import qualified Network.Protocol.TLS.GNU as TLS
+import qualified Data.ByteString.Lazy.Char8 as BC8
 
 import System.IO
 
@@ -54,7 +56,7 @@
   liftIO $ forkIO $ runReaderT a (Thread in' out')
   s - get
   liftIO $ forkIO $ loopWrite s out'
-  liftIO $ forkIO $ connPersist (handle s)
+  liftIO $ forkIO $ connPersist (transport s)
   loopRead in' 
 where 
   loopRead in' = loop $ 
@@ -105,10 +107,20 @@
 else do
   waitFor f
 
-connPersist :: Handle - IO ()
-connPersist h = do
+connPersist :: Transport - IO ()
+connPersist (HandleTransport h) = do
   hPutStr h  
   putStrLn space added
   threadDelay 3000
-  connPersist h
-
+  connPersist (HandleTransport h)
+connPersist (TLSTransport t) = do
+  r - TLS.runTLS t $ do
+TLS.putBytes (BC8.pack  )
+  case r of
+Left x - fail (show x)
+Right _ - return ()
+  putStrLn space added
+  threadDelay 3000
+  connPersist (TLSTransport t)
+  
+
diff -durN -x '*~' -x Test.hs orig/haskell-xmpp-1.0/src/Network/XMPP/Core.hs haskell-xmpp-1.0/src/Network/XMPP/Core.hs
--- orig/haskell-xmpp-1.0/src/Network/XMPP/Core.hs	2011-01-15 16:50:14.0 -0600
+++ haskell-xmpp-1.0/src/Network/XMPP/Core.hs	2012-04-16 21:33:28.101267152 -0500
@@ -26,6 +26,9 @@
 import Network.XMPP.JID
 import Network.XMPP.IQ
 import Network.XMPP.Utils
+import Text.XML.HaXml.Xtract.Parse (xtract)
+import qualified Network.Protocol.TLS.GNU as TLS
+
 
 -- | Open connection to specified server and return `Stream' coming from it
 initiateStream :: Handle
@@ -50,7 +53,48 @@
  
  debug Stream started
  --debug $ Observing:  ++ render (P.content m)
- m - xtractM /stream:features/mechanisms/mechanism/-
+ 
+ -- First, we read stream:features
+ sf_ - xtractM /stream:features
+ let sf = case sf_ of
+   [] - error Did not get stream:features
+   [x] - x
+   x - error Got many stream:features
+   
+ -- Now, we look for starttls.
+ newsf - case xtract id /stream:features/starttls sf of
+   [] - do debug Did not see starttls in features
+return sf
+   x - do debug $ Saw starttls:  ++ show x
+   out $ toContent $ ptag starttls 
+ [xmlns urn:ietf:params:xml:ns:xmpp-tls]
+ []
+   nm - nextM
+   case xtract id /proceed nm of
+ [] - fail Did not get proceed after starttls
+ _ - return ()
+   debug $ Starting TLS
+   session - liftIO $ TLS.runClient (TLS.handleTransport h) $ do
+ TLS.setPriority [TLS.X509]
+ TLS.setCredentials = TLS.certificateCredentials
+ TLS.handshake
+ TLS.getSession
+   case session of
+ Left x - fail (show x)
+ Right x - do 
+   debug $ Got TLS session
+   resetStreamTLS h x
+   debug $ Stream reset
+   out $ toContent $ stream Client server
+   startM
+   tlssf_ - xtractM /stream:features
+   debug $ Got new features
+   return $ case tlssf_ of
+ [] - error Did not get stream:features
+ [x] - x
+ x - error Got many stream:features
+   
+ let m = xtract id /stream:features/mechanisms/mechanism/- newsf
  let mechs = map getText m
  debug $ Mechanisms:  ++ show mechs
 
diff -durN 

[Haskell-cafe] XMPP library recommendations

2012-04-10 Thread John Goerzen

Hi folks,

I'm looking for suggestions for XMPP libraries.  So far I have found 
three on Hackage. Thanks to the authors of these - I think a lot of good 
can come from XMPP in Haskell.


However, all of them appear to be minimally maintained, if at all:

 * XMPP - only one upload, over 2 years ago.  Does not support TLS
   (required by many modern servers).  Does not support SASL (also
   required by many modern servers).  After finding the options on a
   test server to disable the requirements for TLS and SASL, it worked.
 * network-protocol-XMPP - uploaded recently to fix 7.4 build issue,
   not much other recent activity.  Refuses to connect to a test
   account with Received empty challenge (this does not appear to be
   an accurate error message, but rather a bug in XML parsing).  A bit
   more low-level than I'm looking for.
 * haskell-xmpp - only one upload, over 1 year ago.  Connects and
   works.  I like the design.  Is hard-coded to write debug messages to
   stdout, making it a bit of a problem for programs that use stdout
   (though a one-liner mod to the code would fix that).  Says it's
   alpha and work in progress.

What experience do people have with these?  Any recommendations?

Thanks,

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


Re: [Haskell-cafe] where to put general-purpose utility functions

2012-01-25 Thread John Goerzen

Hi Joey,

Apologies for such a late reply.  I don't know if others have replied on 
-cafe; it has become too high-volume for me to follow of late.  There 
are several options.  MissingH is one.  I have accepted patches there 
for a long time.  Another is that now that Hackage/Cabal foster easy 
inclusion of small packages, you might want to roll your own.  
(Occasionally I have hesitation about drive-by commits to MissingH 
because I get asked to support the code later at times.)


-- John

On 01/21/2012 02:20 PM, Joey Hess wrote:

I'm finding a rather unusual problem as I write haskell..

Unlike every other language I've used, large portions of my haskell code
are turning out to be general-purpose, reusable code. Fully 20% of the
haskell code I've written for git-annex is general purpose. Now, I came out
of a decade of perl with maybe 1% reusable code. So I'm sure this is a
credit to haskell, and not to me.

My problem now is that as I start new projects, I want to have my haskell
utility functions available, and copying them around is not ideal. So, put
them on hackage. But where, exactly? It already has several grab bag utility
libraries. The only one with much traction is MissingH. Using the others
makes a program have an unusual dependency, which while only a cabal
install away, would make work for distributions that want to package the
program. I've ruled out using a couple on that basis. Doesn't encourage me
to add another one.

My 2000+ lines of reusable code are a grab-bag of generic utility
functions. Looking them over (see Appendix), I could try to get portions
into existing libraries on hackage, but it's unlikely I'd find a home
for most of them, so I'm still left with this problem of what to do.

I wonder if the model used for xmonad-contrib, of a big library package,
that is very open to additions from contributors, would be helpful here?

John, any interest in moving MissingH in this direction? I get the
impression it's not otherwise changing much lately, and parts of it are
becoming naturally obsolete, maybe this could inject some life into it.
Any other thoughts you have on grab-bag utility libraries on hackage
also appreciated.



Appendix: A sample of a a few of the better functions from my utility library.

   Some quite generic monadic control functions, few of them truely unique:

   whenM :: Monad m =  m Bool -  m () -  m ()   -- also?
   unlessM :: Monad m =  m Bool -  m () -  m () -- also!
   firstM :: Monad m =  (a -  m Bool) -  [a] -  m (Maybe a)

   A module that exports functions conflicting with partial
   functions in the Prelude, to avoid them being accidentially
   used. And provides some alternatives (which overlap somewhat with Safe):

   headMaybe :: [a] -  Maybe a
   readMaybe :: Read a =  String -  Maybe a
   beginning :: [a] -  [a]

   Various path manipulation functions such as:

   dirContains :: FilePath -  FilePath -  Bool
   dotfile :: FilePath -  Bool
   absPath :: FilePath -  IO FilePath

   Other stuff:

   separate :: (a -  Bool) -  [a] -  ([a], [a])
   catchMaybeIO :: IO a -  IO (Maybe a)
   readSize :: [Unit] -  String -  Maybe ByteSize -- parses 100 kb etc
   format :: Format -  Variables -  String
   findPubKeys :: String -  IO GpgKeyIds
   boolSystem :: FilePath -  [CommandParam] -  IO Bool
   withTempFile :: Template -  (FilePath -  Handle -  IO a) -  IO a



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


Re: [Haskell-cafe] New releases and BSD3 license

2011-08-11 Thread John Goerzen

Thanks, Jeremy -- appreciate it!
-- John

On 08/10/2011 02:57 PM, Jeremy Shaw wrote:

Awesome!

I believe MissingH includes some code that I contributed (or used to).
That can all be licensed BSD3.

- jeremy

On Wed, Aug 10, 2011 at 2:14 PM, John Goerzenjgoer...@complete.org  wrote:

Hello,

I would like to announce new versions of the following:

hslogger
convertible
HDBC
HDBC-odbc
HDBC-postgresql
HDBC-sqlite3

By popular, insistent, persistent, and patient requestgrin, all have been
relicensed under the 3-clause BSD license.  I am also working to make that
happen with MissingH, but have to receive permission from a few third
parties first.

Additionally, this will be my last upload of the HDBC* packages. Nicolas Wu
has kindly agreed to step in as HDBC maintainer.  Nicolas has recently
contributed a lot of good things towards HDBC and has more time to maintain
it than I do.

Thanks,

-- John Goerzen

___
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] New releases and BSD3 license

2011-08-10 Thread John Goerzen

Hello,

I would like to announce new versions of the following:

hslogger
convertible
HDBC
HDBC-odbc
HDBC-postgresql
HDBC-sqlite3

By popular, insistent, persistent, and patient request grin, all have 
been relicensed under the 3-clause BSD license.  I am also working to 
make that happen with MissingH, but have to receive permission from a 
few third parties first.


Additionally, this will be my last upload of the HDBC* packages. 
Nicolas Wu has kindly agreed to step in as HDBC maintainer.  Nicolas has 
recently contributed a lot of good things towards HDBC and has more time 
to maintain it than I do.


Thanks,

-- John Goerzen

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


Re: [Haskell-cafe] License of hslogger, HDBC, etc.

2011-06-03 Thread John Goerzen
Nothing particularly lofty; just a realization that other people didn't 
really want to engage in the conversation about LGPL, and I ran out of 
time to do so myself.


-- John

On 06/02/2011 05:07 PM, Vo Minh Thu wrote:

2011/6/2 John Goerzenjgoer...@complete.org:

Hi Jon  all,

I've decided that I'm OK with re-licensing hslogger, HDBC, and well all of
my Haskell libraries (not end programs) under 3-clause BSD.

My schedule is extremely tight right now but if someone wants to send me
patches for these things I will try to apply them within the week.


Thanks!

What was your line of reasoning to make the switch?

Cheers,
Thu




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


[Haskell-cafe] License of hslogger, HDBC, etc.

2011-06-02 Thread John Goerzen

Hi Jon  all,

I've decided that I'm OK with re-licensing hslogger, HDBC, and well all 
of my Haskell libraries (not end programs) under 3-clause BSD.


My schedule is extremely tight right now but if someone wants to send me 
patches for these things I will try to apply them within the week.


-- John

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


Re: [Haskell-cafe] hdbc-odbc adds a space to the value

2011-03-29 Thread John Goerzen

OK, if you send me a tested patch I will be happy to apply it.

-- John

On 03/23/2011 04:09 PM, vagif.ve...@gmail.com wrote:

Latest from hackage: 2.2.3.2

On Wednesday, March 23, 2011 01:58:52 PM you wrote:

  On 03/23/2011 06:43 AM, Gershom Bazerman wrote:

   I've run into that bug too. I'm pretty sure its an issue with

   hdbc-odbc, but haven't wanted to patch it without testing it across a

   few other configurations, which I haven't had time/found

   straightforward to do.

  

   I should add, for those interested, where I think the bug is. In the

   bindCol method of Statement.hsc, there's the following:

  

   rc2 - sqlBindParameter sthptr (fromIntegral icol)

   #{const SQL_PARAM_INPUT}

   #{const SQL_C_CHAR} coltype

   (if isOK rc1 then colsize else fromIntegral cslen + 1) decdigits

   csptr (fromIntegral cslen + 1) pcslen

  

   Either one or both of the fromIntegral csLen + 1 expressions
shouldn't

   have the + 1.

 

  What version of HDBC-ODBC are those of you with the problem running? I

  believe a fix for this was recently checked into my git tree.

 

  -- John

 

   Cheers,

   Gershom

  

  

  

   ___

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


[Haskell-cafe] GHC 7/Cabal request for help

2011-03-24 Thread John Goerzen

Hi folks,

I don't have a GHC 7 environment running yet (it's on my list...) but I 
received a bug report pointing me at this build failure:


http://hackage.haskell.org/packages/archive/testpack/2.0.1/logs/failure/ghc-7.0

Among other things, this noted:

Dependency QuickCheck =2.1.0.3: using QuickCheck-2.4.0.1

and the errors were:

[1 of 3] Compiling Test.QuickCheck.Instances ( 
src/Test/QuickCheck/Instances.hs, dist/build/Test/QuickCheck/Instances.o )


src/Test/QuickCheck/Instances.hs:39:10:
Duplicate instance declarations:
  instance Arbitrary Word8
-- Defined at src/Test/QuickCheck/Instances.hs:39:10-24
  instance Arbitrary Word8 -- Defined in Test.QuickCheck.Arbitrary

src/Test/QuickCheck/Instances.hs:42:10:
Duplicate instance declarations:
  instance CoArbitrary Word8
-- Defined at src/Test/QuickCheck/Instances.hs:42:10-26
  instance CoArbitrary Word8 -- Defined in Test.QuickCheck.Arbitrary

Now, that's fairly standard, and in fact, in my code, is wrapped with:

#if MIN_VERSION_QuickCheck(2,3,0)
-- we have Word8 instances here
#else
instance Arbitrary Word8 where
arbitrary = sized $ \n - choose (0, min (fromIntegral n) maxBound)

instance CoArbitrary Word8 where
coarbitrary n = variant (if n = 0 then 2 * x else 2 * x + 1)
where x = abs . fromIntegral $ n
#endif

And that code has been working to support modern QuickCheck versions for 
some time.


It would appear that something in Cabal, GHC 7, or QuickCheck is 
breaking this check.


Ideas?

-- John

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


Re: [Haskell-cafe] GHC 7/Cabal request for help

2011-03-24 Thread John Goerzen

On 03/24/2011 11:30 AM, Erik Hesselink wrote:

I've just tested this, and with GHC 7, cabal chooses QuickCheck 2.4,
whereas with GHC 6.12, it chooses 2.1. If I specify that 6.12 should
choose 2.4 as well, I get the same issue there. This is to be
expected, because I don't see the CPP checks you mentioned in
Test/QuickCheck/Instances.hs in testpack-2.0.1. Perhaps you haven't
released a version with those checks yet?


Well that would be embarrassing...  but that may indeed be the case.  My 
git tree is marked as if it's released, but apparently it's not.  Sigh. 
 My red-faced apologies for the noise.


-- John

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


Re: [Haskell-cafe] hdbc-odbc adds a space to the value

2011-03-23 Thread John Goerzen

On 03/23/2011 06:43 AM, Gershom Bazerman wrote:

I've run into that bug too. I'm pretty sure its an issue with
hdbc-odbc, but haven't wanted to patch it without testing it across a
few other configurations, which I haven't had time/found
straightforward to do.


I should add, for those interested, where I think the bug is. In the
bindCol method of Statement.hsc, there's the following:

rc2 - sqlBindParameter sthptr (fromIntegral icol)
#{const SQL_PARAM_INPUT}
#{const SQL_C_CHAR} coltype
(if isOK rc1 then colsize else fromIntegral cslen + 1) decdigits
csptr (fromIntegral cslen + 1) pcslen

Either one or both of the fromIntegral csLen + 1 expressions shouldn't
have the + 1.


What version of HDBC-ODBC are those of you with the problem running?  I 
believe a fix for this was recently checked into my git tree.


-- John



Cheers,
Gershom



___
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] HDBC's future and request for help

2011-02-23 Thread John Goerzen

On 02/23/2011 10:03 AM, Leon Smith wrote:

My biggest (mostly) fixable complaint with HDBC is that it hasn't
turned out to be a very complete or robust solution for accessing
databases that like to use PostgreSQL-specific features.   My biggest


This is probably true, both that it isn't designed for database-specific 
features and that this is fixable.



complaint that (probably) isn't easily fixed is it's reliance on
Convertible,  and the use of lots of unsafe pattern matching and
exception-happy functions.


Use of Convertible (or toSql/fromSql which is based on it) isn't really 
required.  You could write a complete HDBC program having never touched 
it, assembling and disassembling your SqlValues manually.  This was a 
design goal of the API.  Convertible makes it easy and convenient for 
the 95% common cases, but you can avoid it if you wish, or use some 
other kind of conversion.  All the HDBC functions work with SqlValues 
(though there are some convenience wrappers that use Strings instead) so 
you can build them up however you like.  SqlValue is documented at 
http://hackage.haskell.org/packages/archive/HDBC/2.2.6.1/doc/html/Database-HDBC.html#t:SqlValue 



If your concern really is with how SqlValue is defined, alternative 
proposals are always entertained ;-)


When you're dealing with databases over a network, exceptions can happen 
just about anywhere.  HDBC does have its own exception type (SqlError) 
so that they can be handled en masse, or picked through more closely if 
desired.  If you have an idea how else that should be handled, I'm all ears.


By unsafe pattern matching do you mean GHC -Wall is flagging pattern 
matches that don't match some possible set of input data, or something 
else?  If the former, that should be trivially fixable too.



At least for the time being,  I've found it easiest and most expedient
to fix up HDBC.   I'm not particularly interested in taking over the
maintenance of HDBC,  and I am comfortable with model #1 at the time
being.   However if somebody else is interested in another option,
I'm probably ok with that too.


Thanks for your feedback, Leon.  I've appreciated your patches.

-- John

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


Re: [Haskell-cafe] HDBC's future and request for help

2011-02-23 Thread John Goerzen

On 02/23/2011 05:48 AM, Chris Dornan wrote:

The simple answer is that I need to be able to use HDBC in proprietary
products and the LGPL makes this awkward – the most serious issue being
that owners of the code base don’t want GNU licensed parts being linked
into their code base. Packaging and delivery also gets complicated – (as
I understand it) LGPL components can’t be delivered pre-linked,
necessitating dynamic linking of the relevant libraries or supplying a
GHC kit which the customer must use to assemble the product. This is all
a significant drag.


Let's talk about specifics.  I imagine that in LGPL-3 that the only 
clause for objection here is 4(d)0, which requires that the proprietary 
application be conveyed in a form such that the user can relink it with 
a modified version of the library.


I would be willing to add an exemption to that requirement to the HDBC 
license, which should address that concern.


What do you think?


Also, wouldn’t it be good to get HDBC into the Haskell Platform? – but
we can’t do this while it is LGPL can we?


Why not?


On the other side, what are the risks with adopting a BSD license? Is it
that somebody could fork the library into a proprietary Haskell DB
library that would compete with HDBC?


That's one way to put it.  It's a big complaint I have about the BSD 
license.  There are many, many examples of companies taking things 
licensed under BSD, adding features small or large, selling the result 
at profit, and neither releasing the source for the new features to the 
community nor compensating the original authors in any way.


I see a distinction between someone that just wants to *use* HDBC and 
between someone that wants to embrace and extend it.


I know that work I do on Linux, Haskell, etc. leads to companies such as 
Ubuntu making a profit off my work, for which they don't compensate me. 
 I also know that if they improve on it, and it's GPL, they have to 
return those improvements to the community so we can all benefit.


I am bothered by the notion of letting companies take work I've done on 
a volunteer basis, close it up, change it, never compensate me for it 
and also never release the changes to the community.  This is why I 
prefer to avoid the BSD license.


In the case of HDBC, if all somebody wants to do is use vanilla HDBC in 
their program without having to release the source to the proprietary 
program or jump through hoops to let end users replace HDBC, then I 
think that LGPL with the modification I proposed above would meet both 
their concern and mine.  The LGPL would still require them to note 
HDBC's copyright (which the BSD license requires as well), and to 
distribute source to any modifications they make *to HDBC*, but impose 
no other onerous restrictions if my reading is correct.


- John

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


Re: [Haskell-cafe] HDBC's future and request for help

2011-02-23 Thread John Goerzen

On 02/23/2011 11:57 AM, Chris Dornan wrote:

Thanks John,

I think this is a valuable discussion.

The compromise you propose wouldn’t address the main point – the fear
and aversion of using (L)GPL IP in proprietary IP.


Is that fear well-grounded or not?  If not, then people should be 
educated.  If so, then let's see what we can do about it -- either add 
exceptions or relicense.  I don't really think that this community 
should choose licenses based upon whether or not third parties hold an 
irrational fear of them.



For me the key phrase in your email was the final one – ‘if my reading
is correct’. Everywhere I would take advantage of this modified license
I will need to get the lawyers of the people owning the host IP to agree
to this interpretation.


This is no different than with any other license, but could even be made 
more explicit.  In the end, we are (mostly) a community of non-lawyers 
here so such disclaimers


I also don't think that we ought to cater to people who are afraid to 
read licenses.  Those are the people that tend to do things like pirate 
busybox and the Linux kernel for proprietary purposes.



I have checked all of the packages in the Haskell Platform and they are
all BSD3. If it had been otherwise it would have destroyed a significant
part of the value of the HP – clear and straightforward licensing
implications for using it.


And that is a useful point as well.  If there is a big package that 
people can use and understand once, without having to analyze licenses 
for dozens of component packages, there's value in that for sure.


There are two ways to accomplish that.  One is to insist that everything 
use the same license.  The other is to establish standards for what kind 
of licensing terms are acceptable.  An example of the latter is the 
Debian Free Software Guidelines, 
http://www.debian.org/social_contract#guidelines


We could propose a guideline for things that go in the Haskell Platform, 
and it could be such as this:


* All licenses must meet the terms of the Debian Free Software 
Guidelines (DFSG), and must also meet the following terms:


* Proprietary applications may use and link with unmodified versions of 
libraries without forcing the rest of the application to use a specific 
license


* Licenses may require proprietary applications that use and link with 
modified versions of libraries to make source code to the modifications 
available to the community under the original library's license, but may 
not require applications to do so for other code linked to the application


* Licenses may require copyright and/or warranty disclaimers to be 
carried with applications that use the code.


Perhaps we could also list example copyright/license statements that 
meet the requirements.



I really don’t want to plough work into a package that can’t be bundled
with the HP, the natural home for strategically-important high-quality
libraries.


I'm not certain the HP is a good home for HDBC.  One could put HDBC 
itself in there, but it's useless without a database backend.  All of 
those, do date, require a C binding which probably makes them poor 
candidates for the HP.  If the thing in the platform is useless without 
the backend driver, is it sensible to put it in the HP?


At the same time, if one of the HP maintainers says, We want HDBC in 
the HP and all that's holding us back is the license I think that would 
be compelling enough for me to switch it immediately.



Turning this around, it is going to be much easier to get people who are
using Haskell in commercial contexts to contribute to HDBC if it has a
license that meets their requirements.


Quite so.  I want to make sure we do that.  That's one reason I have 
kept the door to the BSD license open.  As I've said, I've relicensed 
other code under BSD in the past and may be convinced to do it again. 
What I'm hoping the commercial people on this list could do (besides me, 
that is) is say something like LGPL won't work for us because clause 
xxx requires us to do yyy.


Then we can have a good discussion here, revolving around:

 * Is the community/author prepared to say that we want to let people 
do yyy with our software?
 * And if so, what is the best response?  Can we make small exceptions 
to the LGPL to satisfy it, or do we have to go to the BSD or some other 
such license?



I do appreciate your concerns – I have regularly contributed code to the
community and want to continue doing so – but I think there is little
real prospect of HDBC being attacked by a proprietary derivative. I
don’t doubt there will be some free-loading, but this might be the
inevitable price of attracting more investment.


That's an interesting point.  There is, of course, free-loading even 
with GPL'd software.  The promise there is, though, that people get 
their rights preserved regardless of who gives them the software.  I 
like that, and think that in the long term it produces the greatest net 
gain in 

[Haskell-cafe] HDBC's future and request for help

2011-02-22 Thread John Goerzen

Hi folks,

HDBC has been out there for quite some time now.  I wrote it initially 
to meet some specific needs, and from that perspective, it has been done 
for awhile.  It is clear, however, that there are some needs it doesn't 
meet.  Most of them relate to specific backend driver items.


I'd like to start some discussion in the community about what the future 
of HDBC and its backend drivers ought to look like.  Some models might be:


 1. I continue as maintainer for HDBC and 
HDBC-{postgresql,odbc,sqlite3} and act as patch manager/gatekeeper for 
patches that are discussed on some public mailing list.


 2. Interested parties adopt the backend drivers while I continue to 
act as maintainer/patch manager/gatekeeper for HDBC itself.


 3. Interested parties adopt all of HDBC and maintain it

I am not expressing a particular preference for any of these options; 
just putting them forth.


Here are some of the current issues I am aware of:

 1. I have no Windows development platform.  I can't test the releases 
on Windows.  Many Windows users don't have the skill to diagnose 
problems.  These problems do eventually get fixed when a Windows user 
with that skill comes along -- and I appreciate their efforts very much! 
-- but it takes longer than it ought to.


 2. The ODBC documentation is monumentally terrible, and the API is 
perhaps only majestically terrible, and it is not 100% clear to me all 
the time that I have it right.  A seasoned ODBC person would be ideal here.


 3. Issues exist with transferring binary data and BLOBs to/from at 
least PostgreSQL databases and perhaps others.  There appear to be bugs 
in the backend for this, but BLOB support in the API may need to be 
developed as well.


 4. Although the API supports optimizations for inserting many rows at 
once and precompiled queries, most backends to not yet take advantage of 
these optimization.


 5. I have received dueling patches for whether foreign imports should 
be marked safe or unsafe on various backends.  There seems to be 
disagreement in the community about this one.


 6. Many interactions with database backends take place using a String 
when a more native type could be used for efficiency.  This project may 
be rather complex given varying types of column data in a database -- 
what it expects for bound parameters and what it returns.  The API 
support is there for it though.


 7. Various other more minor items.

Thoughts?

-- John

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


Re: [Haskell-cafe] HDBC's future and request for help

2011-02-22 Thread John Goerzen

On 02/22/2011 01:33 PM, Chris Dornan wrote:

Hi John,

Two thoughts: is there any prospect of making HDBC available under a
BSD-like license? The LGPL license is a significant barrier for me and I
expect it will be for others.


I'm happy to discuss this with people.  It would be helpful to 
understand concrete cases where this would be a problem.  I have 
permitted other code to be relicensed under BSD in the past and so don't 
have a huge hangup about this.  If it's the best thing for the 
community, I'd be likely to do it.  On the other hand, I have seen 
numerous cases over the years where BSD code has been taken by some 
company and essentially forked into a proprietary version.  I feel this 
is not in the long-term interests of the community, and that drawback 
has to be weighed against any advantage.



And, along the lines of your own comments, the ODBC interface raises a
significant (technical) barrier for MySQL users. Is there any chance
that we can encourage/help getting the the MySQL driver closer to
production quality?


The short answer is probably to send patches to its author or fork it. 
Or fund someone else to do so.


-- John

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


Re: [Haskell-cafe] HDBC, postgresql, bytestrings and embedded NULLs

2011-01-17 Thread John Goerzen

On 01/17/2011 10:07 AM, Michael Snoyman wrote:

On Mon, Jan 17, 2011 at 4:49 PM, Leon Smithleon.p.sm...@gmail.com  wrote:

On Sat, Jan 8, 2011 at 11:55 AM, Michael Snoymanmich...@snoyman.com  wrote:


In general I think it would be a good thing to have solid, low-level bindings 
to PostgreSQL.


Well, there is PostgreSQL and libpq on hackage:

http://hackage.haskell.org/package/libpq
http://hackage.haskell.org/package/PostgreSQL

The PostgreSQL looks like it's in need of maintenance,  and hasn't
been updated in a few years.   libpq is new,  and looks promising.   I
haven't really used either one, so I can't really say too much about
either.

Best,
Leon



I've tried PostgreSQL before, and if I remember correctly I couldn't
even build it. libpq looks interesting, I'd like to try it out.
Unfortunately it depends on unix, which would be a problem for Windows
users. If it looks like a good fit for persistent-postgresql, maybe I
can convince the author to replace the unix dep with something else
(unix-compat might be sufficient).


I would also like to know what things people find are deficient in HDBC 
or HDBC-postgresql.  If the API isn't good enough for some uses, that 
could be fixed.  I would like to avoid a proliferation of database 
libraries as that is unnecessary duplication of work.  HDBC does have an 
easy way for DB backends to implement more functionality than the HDBC 
API supports, or an alternative could also be to make HDBC-postgresql a 
thin binding over libpq or some such.


-- John



Thanks for the pointer,
Michael

___
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] HDBC, postgresql, bytestrings and embedded NULLs

2011-01-17 Thread John Goerzen

On 01/17/2011 03:16 PM, Michael Snoyman wrote:

I've brought up before my problem with the convertible package: it
encourages usage of partial functions. I would prefer two typeclasses,
one for guaranteed conversions and one for conversions which may fail.
In fact, that is precisely why convertible-text[1] exists.


I would be open to making that change in convertible.  The unfortunate 
reality with databases, however, is that many times we put things into 
strings for sending to the DB engine, and get things back from it in the 
form of strings, which must then be parsed into numeric types and the 
like.  We can't, as a matter of type system principles, guarantee that a 
String can be converted to an Integer.  How were you thinking the 
separation into these typeclasses would be applied in the context of 
databases/



As a related issue, there are a large number of data constructors in
HDBC for SqlValue. I would not argue with the presence of any of them:
for your purposes, every one of them is necessary. But for someone
writing a cross-backend package with a more limited set of datatypes,
it gets to be a problem. I know I can use convertible for this, but
see my previous paragraph ;).


How about using an import...hiding statement?  Perhaps even your own 
module that only re-exports the constructors you like?



I also don't like using the lazy result functions. I'm sure for many
people, they are precisely what is needed. However, in my
applications, I try to avoid it whenever possible. I've had bugs crop
up because I accidently used the lazy instead of strict version of a
function. I would prefer using an interface that uses enumerators[2].


It would be pretty simple to add an option to the API to force the use 
of the strict versions of functions in all cases (or perhaps to generate 
an exception if a lazy version is attempted.)  Would that address the 
concern?  Or perhaps separating them into separate modules?


I took a quick look at the enumerators library, but it doesn't seem to 
have the necessary support for handling data that comes from arbitrary C 
API function calls rather than handles or sockets.



For none of these do I actually think that HDBC should change. I think
it is a great library with a well-thought-out API. All I'm saying is
that I doubt there will ever be a single high-level API that will suit
everyone's need, and I see a huge amount of value in splitting out the
low-level code into a separate package. That way, *everyone* can share
that code together, *everyone* can find the bugs in it, and *everyone*
can benefit from improvements.


Splitting out the backend code is quite reasonable, and actually that 
was one of the goals with the HDBC v2 API.  I would have no objection if 
people take, say, HDBC-postgresql and add a bunch of non-HDBC stuff to 
it, or even break off the C bindings to a separate package and then make 
HDBC-postgresql an interface atop that.


I hope that we can, however, agree upon one low-level database API.  The 
Java, Python, and Perl communities, at least, have.  Failing to do so 
produces unnecessary incompatibility.


I would also hope that this database API would be good enough that there 
is rarely call to bypass it and use a database backend directly.


-- John

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


Re: [Haskell-cafe] HDBC, postgresql, bytestrings and embedded NULLs

2011-01-07 Thread John Goerzen

On 01/07/2011 05:24 AM, Michael Snoyman wrote:

On Fri, Jan 7, 2011 at 11:44 AM, Iustin Popius...@google.com  wrote:
Yes, I had a bug reported in persistent-postgresql that I traced back
to this bug. I reported the bug, but never heard a response. Frankly,
if I had time, I would write a low-level PostgreSQL binding so I could
skip HDBC entirely.


I'm not seeing an open issue at 
https://github.com/jgoerzen/hdbc-postgresql/issues -- did you report it 
somewhere else?


What would you gain by skipping HDBC?  If there's a problem in the API, 
I'd like to fix it.


-- John

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


Re: [Haskell-cafe] HDBC, postgresql, bytestrings and embedded NULLs

2011-01-07 Thread John Goerzen

On 01/07/2011 09:49 AM, John Goerzen wrote:

On 01/07/2011 05:24 AM, Michael Snoyman wrote:

On Fri, Jan 7, 2011 at 11:44 AM, Iustin Popius...@google.com wrote:
Yes, I had a bug reported in persistent-postgresql that I traced back
to this bug. I reported the bug, but never heard a response. Frankly,
if I had time, I would write a low-level PostgreSQL binding so I could
skip HDBC entirely.


I'm not seeing an open issue at
https://github.com/jgoerzen/hdbc-postgresql/issues -- did you report it
somewhere else?


Along the same lines, I am a volunteer and patches are accepted even 
more happily than bug reports.  It's disheartening to see someone's 
volunteer work reduced to Bah, it doesn't escape NULLs, so it sucks so 
much that I'll just go write my own.  It would seem to me that 
contributing your skill to fixing issues with existing software would be 
a better thing than having to invent yet another database system.


-- John

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


Re: [Haskell-cafe] GHC 7.0.1 developer challenges

2010-12-08 Thread John Goerzen

On 11/29/2010 03:00 PM, John D. Ramsdell wrote:

only one other solution.  Somehow the default behavior of the runtime
system must impose some reasonable limit.  Here is the problem with


Shouldn't you configure your operating system to impose some reasonable 
limit?  That's not the job of the programming language in any other 
language I know of (exception: Java).


See, for instance, ulimit on *nix machines.

-- John

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


[Haskell-cafe] Re: HDBC/ODBC using mysql appears broken...

2010-11-04 Thread John Goerzen

On 11/04/2010 01:39 PM, Neil Davies wrote:

Hi

I've been trying to get the hello world example below to work:

main = do
  db- connectODBC connect'string
  get   Tables db= print


I wonder if you might try something other than getTables, which requires 
some metadata support on the backend?  Some simple inserts orselects, 
perhaps?

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


Re: [Haskell-cafe] Re: HDBC/ODBC using mysql appears broken...

2010-11-04 Thread John Goerzen

On 11/04/2010 04:03 PM, Neil Davies wrote:

John

simple queries seem to work fine.

main = do
   db- connectODBC connect'string
   quickQuery db select serial from CPE_DEVICE []= print . take 3
   describeTable db CPE_DEVICE


I'm going to guess that the MySQL ODBC driver isn't implementing the 
metadata stuff, which is kind of weak in ODBC in general.


Can I interest you in PostgreSQL or Sqlite3? ;-)

- John



returns

[[SqlByteString 1MD16BBV00F74],[SqlByteString 1MD16BB700D03],[SqlByteString 
1MD16BBH02DCD]]
*** Exception: Prelude.(!!): index too large

if that helps..

Neil

On 4 Nov 2010, at 19:41, John Goerzen wrote:


On 11/04/2010 01:39 PM, Neil Davies wrote:

Hi

I've been trying to get the hello world example below to work:

main = do
  db- connectODBC connect'string
  get   Tables db= print


I wonder if you might try something other than getTables, which requires some 
metadata support on the backend?  Some simple inserts orselects, perhaps?
___
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] who's in charge?

2010-10-28 Thread John Goerzen

On 10/27/2010 10:08 AM, Günther Schmidt wrote:

Dear Malcolm,

since there is no mail client library even after 10+ years I suggest to
rethink the approach, because frankly, it's not working.


Why do you keep suggesting this?

http://hackage.haskell.org/package/WashNGo

There is no need for a mail client library on many platforms.  Just pipe 
the data to /usr/sbin/sendmail and poof.  Done.


Has it occurred to you that there is no mail client library because 
there is no need for one?  Frankly I am unimpressed with monster 
10,000-SLOC mail client libraries that make it a lot harder for me to 
pipe some stuff to sendmail.


-- John



Günther
___
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] who's in charge?

2010-10-28 Thread John Goerzen

On 10/27/2010 11:55 AM, Ketil Malde wrote:

What does essential mean?  Something a hypothetical dictator wants,
but nobody else?  For surely, if your email library was so essential,
it'd be included among the hundreds of libraries on Hackage?  Perhaps it
is a lot less important than you think?  (None of my programs need to
send email, so it's certainly not essential to me.)

Or perhaps sufficient functionality is in the libraries suggested by
Michael, and you just didn't find it when you looked?


The third option is that sending mail is so ridiculously simple that no 
library is needed.  This is, at least, the case for plain text messages 
on *nix.


I will grant that when you toss MIME and Windows into the mix, 
s/simple/complex/ may become more appropriate.


But we do already have MIME libraries.

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


Re: [Haskell-cafe] If Python now has a good email library; how challenging is it to call Python from Haskell?

2010-10-28 Thread John Goerzen

On 10/27/2010 01:22 PM, Donn Cave wrote:

Don't know, but probably challenging enough to make it worth challenging
the assumption that Python now has a good email library.


From a cursory look at the 3.0 library documentation, it looks to

me like IMAP support still means the old imaplib module.  That's
pretty rudimentary, compared to the HaskellNet IMAP support.


Not just rudimentary, but hideously buggy and with a terrible API. 
imaplib2 improves the API a bit but makes the bugginess worse.


I wrote and maintained OfflineIMAP from 2001 (I think) to 2010 so have 
just a wee bit of experience with that issue.


Python's mail system is not strong in my book.  It barely scrapes by. 
The MIME bits are decent, but the mail client stuff is very poor.  There 
is no abstraction system over generic mailbox repositories IIRC.  If you 
want to support IMAP, POP, Maildirs, mboxes, etc. you have to code up 
support for each.


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


Re: [Haskell-cafe] who's in charge?

2010-10-28 Thread John Goerzen

On 10/28/2010 05:44 PM, Günther Schmidt wrote:

There is no need for a mail client library on many platforms. Just
pipe the data to /usr/sbin/sendmail and poof. Done.


That would work well for sending (on Unix), but not for receiving.


Quite true.  For receiving, we have tools like fetchmail, imapsync, 
offlineimap, MH, the list goes on.


The Unix philosophy is all about pluggable bits and pieces that can be 
reused all over the place.  I like that philosophy.  It means that one 
doesn't have to reinvent mail handling n times for n languages.  As long 
as your language can do some piping, you can handle the basics of mail.


Now, I'll grant you that fetchmail won't solve every possible mail 
access scenario.  It isn't, for instance, good enough to be the backend 
of OfflineIMAP.  But I do want to push back on the notion that, on POSIX 
platforms, these things have to be reinvented for each language.  It 
just isn't so.



Has it occurred to you that there is no mail client library because
there is no need for one?


No, to be honest, it never has. I absolutely cannot conceive of it. It'd
be like not having HDBC for instance and having to roll my own database
driver. It wouldn't have mattered how great a language haskell is, had


Hmm, I am perhaps uniquely qualified to say been there, done that ;-)

The existing Haskell database drivers at the time didn't meet my needs. 
 They lacked some things I considered rudimentary and standard.  I felt 
about them approximately the way you did about mail.


I decided that Haskell would be enough of a long-term win to justify 
writing HDBC.  So I did, and I'm glad of it.


I think you are getting some resistance here because you appear to be 
demanding that others volunteer their time to meet your pet need.  This 
attitude doesn't usually work.



it not had HDBC I would have had no choice but to drop it and move on.


Or you could have written HDBC.  Or you could have used unixODBC, which 
already solved that problem.  (Whoops, did I do a tiny bit of wheel 
reinvention myself?  Indeed I did, with the PostgreSQL HDBC backend. 
There are reasons for it though.)



Database connectivity to me is one of the essential things I need to be
able to do, and so is email, as is xml, as is http.


HTTP is another thing that can easily be outsourced.  I've been 
somewhat unhappy at various points in time with the Haskell HTTP 
libraries.  No problem, though; there's always Curl.  One can choose the 
Haskell libcurl binding or call the Curl binary directly; it's even 
portable to all sorts of platforms, and you get not just HTTP, but FTP, 
Gopher, SCP, and some other useful protocols along for the ride.



Well it's not necessarily only about sending mail, it's more about the
whole shebang one wants / needs to do with mail.


So if it's not about sending, it's about receiving or accessing stored mail.

The Maildir spec is very simple and easily implemented.  Google tells me 
there is an implementation in xmonad already.  Tools to get mail into 
Maildirs are plentiful and featureful.


My point is this: using existing tools on your system, and turning a 
blind eye to their implementation language, can be a perfectly workable, 
and even elegant, solution.


Example: say you needed to copy a directory containing files and 
directories.  Is that easy to do?  You could probably whip up some sort 
of recursive file copying thing to do that in a few lines of code.  But 
will it handle things like preserving permissions bits, ownership, ACLs, 
symbolic links, not following symlinks, etc. correctly?  We already have 
a tool that does all those things (cp -a), so using it is, in my book, 
more elegant than writing a (probably more buggy and certainly less 
tested) clone.


So I'm pushing back on your unstated premise; namely, that a Haskell 
library for mail handling is necessary for efficient mail handling in 
Haskell.  I don't think it is.


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


Re: [Haskell-cafe] who's in charge?

2010-10-28 Thread John Goerzen

On 10/28/2010 07:48 PM, Daniel Peebles wrote:

Would anyone be interested in a project for a full-featured mail
library? I don't think I'm capable of writing the whole thing
myself, but I've started a github project at URL and would be happy
to collaborate in IRC channel #channel on freenode.


Would have resulted in a very different response.


That is absolutely well put.

Günther, I don't condone hostility on the part of anyone on this list, 
obviously.  If you experienced it, it's not right.


By the same token, you came in here talking about escalating a 
problem, and saying that an entire process was fundamentally broken 
because you hadn't found a solution to your particular problem.


What people are trying to tell you is:

1) That argument isn't well-formed, because that conclusion doesn't 
follow from the premise.  In other words, your pet problem may not 
indicate a bad community/process.


2) This is a doocracy (man do I hate that word!).  If there is a 
problem, here's what you should do about it, in descending order of 
attractiveness:


a) Fix it yourself

b) Pay someone else to fix it

c) Motivate or politely encourage others to fix it, providing moral 
support, etc.


The key point is: you haven't paid any of us for this, and you have 
nothing even close to some sort of support contract.  I perceive a sense 
of entitlement on your part that people owe you no-cost coding.  That's 
just not how the community works.  Whether or not you really have that 
sense, I don't know, but your messages convey it nonetheless.


3) There are several existing solutions for doing mail in Haskell, and 
those of us that have used them have, to date, found them perfectly 
adequate.


a) Some of them Google or hackage searches could have informed you of. 
You should do more research before insulting an entire community.


b) It is, of course, possible that these solutions don't meet your 
needs.  In that event, see #2.



On a personal note, some of you with moderately long and extremely sharp 
memories, or perhaps access to Google, may find some messages from me in 
my early Haskell days grousing about this or that problem.  Ultimately, 
the questions for me were:


1) Is the problem real?  In other words, was there simply something I 
didn't know/understand about the language that would have made it go away?


2) Can I fix it?  If so, I should try.

3) How annoying is it?

I wrote some of my libraries when I was still a Haskell newbie (and with 
the number of Ph. D's around here, I'm not always sure I've shed that 
title yet!)... sometimes that shows in the older code that's out there. 
 But that's OK; it solved my problem and, truly, I had fun writing them.


Sometimes it is easier to write a Haskell library to solve the problem 
than to use an off-the-shelf library in $LANGUAGE.


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


[Haskell-cafe] Re: HDBC-postgresql and safe/unsafe FFI calls

2010-09-03 Thread John Goerzen

On 09/03/2010 06:14 PM, David Powell wrote:

Hi John,

My current usage of hdbc is in a server process that takes requests from
multiple clients, queries the database, and returns a result.  Having a
single db query block everything else isn't really workable for me.  I
suspect this will also be an issue for others.  As an example, the
persistent-postgresql package which is part of the new Yesod web
framework will have the same problem.

I can send you a patch, but I am concerned with the issue Leon raised
about libpq needing to be compiled with thread support.  This is the
default on my platforms (macosx, debian), but probably is dangerous to
rely on.  I guess we can just test the result of 'PQisthreadsafe()', in
connectPostgreSQL and raise an error if it is false.


Or at least a warning to stderr -- that won't be a problem for 
single-threaded programs, right?




Cheers,

-- David


On Fri, Sep 3, 2010 at 1:36 AM, John Goerzen jgoer...@complete.org
mailto:jgoer...@complete.org wrote:

Hi David,

I've had varying arguments from people that want me to mark things
safe or unsafe for various performance reasons.  I'm happy to apply
your change if you like.  Can you send me a diff (and attach your
explanation here to it, which I'll use as a commit message for
future reference)?

Thanks,

-- John


On 09/01/2010 09:40 PM, David Powell wrote:

Greetings,

I'm having an issue with the HDBC-postgresql package that
requires me to
manually patch it before installation for most of my use cases.

All the FFI calls in this package are marked unsafe.
  Unfortunately,
this means that whenever I issue a slow sql query, all other
processing
stops.  In most places that I want to use this module, I've had to
manually patch it to at least mark the PQexec and PQexecParams
calls as
safe.

Is there any reason these calls should not be marked as safe?  I
understand that there a little extra runtime overhead with this,
but I'd
have thought that negligible given all the other processing that
goes on
with these particular calls under the hood.

Cheers,

--
David Powell





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


[Haskell-cafe] Re: HDBC-postgresql and safe/unsafe FFI calls

2010-09-02 Thread John Goerzen

Hi David,

I've had varying arguments from people that want me to mark things safe 
or unsafe for various performance reasons.  I'm happy to apply your 
change if you like.  Can you send me a diff (and attach your explanation 
here to it, which I'll use as a commit message for future reference)?


Thanks,

-- John

On 09/01/2010 09:40 PM, David Powell wrote:

Greetings,

I'm having an issue with the HDBC-postgresql package that requires me to
manually patch it before installation for most of my use cases.

All the FFI calls in this package are marked unsafe.  Unfortunately,
this means that whenever I issue a slow sql query, all other processing
stops.  In most places that I want to use this module, I've had to
manually patch it to at least mark the PQexec and PQexecParams calls as
safe.

Is there any reason these calls should not be marked as safe?  I
understand that there a little extra runtime overhead with this, but I'd
have thought that negligible given all the other processing that goes on
with these particular calls under the hood.

Cheers,

--
David Powell


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


Re: [Haskell-cafe] Merge hsql and HDBC -- there can only be one!

2010-07-21 Thread John Goerzen

On 07/20/2010 11:45 PM, Michael Snoyman wrote:

I think a simple statement along the lines of the GNU Classpath linking
exception would go very far[1]. I only mention that one since it's
quoted verbatim on the Wikipedia site.

Michael

[1]
http://en.wikipedia.org/wiki/GPL_linking_exception#The_classpath_exception


That one pertains to GPL, not LGPL.  The issues with each are different. 
 HaXml, however, has this:


As a relaxation of clause 6 of the LGPL, the copyright holders of this
library give permission to use, copy, link, modify, and distribute,
binary-only object-code versions of an executable linked with the
original unmodified Library, without requiring the supply of any
mechanism to modify or replace the Library and relink (clauses 6a,
6b, 6c, 6d, 6e), provided that all the other terms of clause 6 are
complied with.

I need to read the LGPL and analyze it closer, but my first analysis 
suggests that this would work fine for me and others.


wxHaskell uses:

  EXCEPTION NOTICE

  1. As a special exception, the copyright holders of this library give
  permission for additional uses of the text contained in this release of
  the library as licenced under the wxWindows Library Licence, applying
  either version 3 of the Licence, or (at your option) any later version of
  the Licence as published by the copyright holders of version 3 of the
  Licence document.

  2. The exception is that you may use, copy, link, modify and distribute
  under the user's own terms, binary object code versions of works based
  on the Library.

  3. If you copy code from files distributed under the terms of the GNU
  General Public Licence or the GNU Library General Public Licence into a
  copy of this library, as this licence permits, the exception does not
  apply to the code that you add in this way.  To avoid misleading 
anyone as

  to the status of such modified files, you must delete this exception
  notice from such code and/or adjust the licensing conditions notice
  accordingly.

  4. If you write modifications of your own for this library, it is your
  choice whether to permit this exception to apply to your modifications.
  If you do not wish that, you must delete the exception notice from such
  code and/or adjust the licensing conditions notice accordingly.

I'll also want to evaluate LGPL v3, which I have been meaning to move to 
anyhow.


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


Re: [Haskell-cafe] Merge hsql and HDBC -- there can only be one!

2010-07-20 Thread John Goerzen

On 07/07/2010 03:22 PM, Don Stewart wrote:


And you have to be wary about the license of HDBC (LGPL) if you want to
use the package in software you redistribute (though this is rarely the
case for database apps, I'm guessing). Satisfying the linking
requirements with GHC -O2 are non-trivial, even with -dynamic.


I remain ready to have a discussion with anyone that has a problem with 
that.  I've had one or two people ask me about it in the past, but they 
never followed up to my reply mails.  I'm not going to be a stick in the 
mud about LGPL, but neither do I want to allow others to 
commercialize/embrace-and-extend HDBC without giving back to the 
community.  My intent isn't to get in the way of people using HDBC in 
their own software, whether commercial or proprietary, but to prevent 
proprietarization of HDBC itself.  I suspect LGPL+some exemption could 
solve any concerns and would be happy to pursue it.




-- Don



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


Re: [Haskell-cafe] The instability of Haskell libraries

2010-04-26 Thread John Goerzen

On 04/25/2010 03:47 PM, Ivan Lazar Miljenovic wrote:

So you recommend having packages specifically for instances?

My main problem with this is if you want a custom variant of that
instance.  Let's take FGL graphs for example with instances for
QuickCheck's Arbitrary class.  Maybe you want arbitrary graphs that are
simple, or maybe multiple edges are fine.  Even when considering
Arbitrary instances for something like String you may wish to have a
custom variant that makes sense for what you're testing.

My conclusion: it is not possible to have hard-and-fast conclusions for
things like this :p


I'm inclined to agree.  As an example, there is the convertible library. 
 It grew out of the need to make an easy way to map Haskell to database 
types in HDBC, and these days is a more general way to convert from one 
type to another.  I provide a bunch of Convertible instances, but they 
are in separate modules, and thus can be omitted if a person doesn't 
want the instances.  As an example: what's the correct way to convert a 
Double to an Integer?  As an example, Prelude defines at least 4: 
ceiling, floor, truncate, and round.


Now, in a certain sense, Convertible is designed for people that don't 
care which is used.  (And yes, that is a perfectly valid answer in some 
cases.)  But if you want your own, you can simply not import the numeric 
Convertible instances.


It would, however, be nice if the language allowed you to override 
default instances with the code in your own package.


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


Re: [Haskell-cafe] Compressing GHC tarballs with LZMA

2010-04-24 Thread John Goerzen

Magnus Therning wrote:

On 24/04/10 08:02, Bulat Ziganshin wrote:

Hello Leon,

Saturday, April 24, 2010, 12:23:58 AM, you wrote:


file nearly a third smaller.   Given that many modern variants of the
tar command support .tar.lzma files directly

isn't latest version of lzma-based compression use .xz extension?


How common is support for .xz on the platforms we are interested in here?

I just passed a .tar.xz to a Mac user and got an email back that he couldn't
unpack it.  Rather than dig deeper I just sent him a .tar.gz, so I don't know
what tool he was using.


Not very.  dpkg may support it in the future, but that is a somewhat 
closed platform where Debian folks are in charge of both the archive and 
the tool used to unpack it.


I would be shocked to find xz preinstalled on a MacOS, AIX, or Solaris 
box.  That even goes for bzip2 on some of those platforms.


(At least we seem to be beyond the days when we still had to provide .Z 
files...)

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


[Haskell-cafe] Unicode strings and runCommand / runProcess

2010-04-23 Thread John Goerzen

Here is a very interesting little problem.

ghci
GHCi, version 6.12.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Prelude :m System.Process
Prelude System.Process runCommand echo привет
?...@825b

This is a minimal test case for a bug reported in HSH at 
http://github.com/jgoerzen/hsh/issues#issue/1


It is not entirely clear to me what the behavior here should be.  It 
seems inconsistent with the default behavior of System.IO to, 
apparently, just strip the bits higher than 0xFF.  On the other hand, 
when it's OS commands we're talking about, it's not entirely clear to me 
if the default should be to encode in UTF-8.  There should almost 
certainly be an *option* controlling this, and perhaps a version of 
runProcess that accepts ByteStrings.


Thoughts?

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


[Haskell-cafe] The instability of Haskell libraries

2010-04-23 Thread John Goerzen
It is somewhat of a surprise to me that I'm making this post, given that 
there was a day when I thought Haskell was moving too slow ;-)


My problem here is that it has become rather difficult to write software 
in Haskell that will still work with newer compiler and library versions 
in future years.  I have Python code of fairly significant complexity 
that only rarely requires any change due to language or library changes. 
 This is not so with Haskel.


Here is a prime example.  (Name hidden because my point here isn't to 
single out one person.)  This is a patch to old-locale:


Wed Sep 24 14:37:55 CDT 2008  xx...@x.
  * Adding 'T' to conform better to standard
  This is based on information found at

http://en.wikipedia.org/wiki/ISO_8601#Combined_date_and_time_representations
diff -rN -u old-old-locale/System/Locale.hs new-old-locale/System/Locale.hs
--- old-old-locale/System/Locale.hs 2010-04-23 13:21:31.381619614 -0500
+++ new-old-locale/System/Locale.hs 2010-04-23 13:21:31.381619614 -0500
@@ -79,7 +79,7 @@
 iso8601DateFormat mTimeFmt =
 %Y-%m-%d ++ case mTimeFmt of
  Nothing  - 
- Just fmt - ' ' : fmt
+ Just fmt - 'T' : fmt

A one-character change.  Harmless?  No.  It entirely changes what the 
function does.  Virtually any existing user of that function will be 
entirely broken.  Of particular note, it caused significant breakage in 
the date/time handling functions in HDBC.


Now, one might argue that the function was incorrectly specified to 
begin with.  But a change like this demands a new function; the original 
one ought to be commented with the situation.


My second example was the addition of instances to time.  This broke 
code where the omitted instances were defined locally.  Worse, the 
version number was not bumped in a significant way to permit testing for 
the condition, and thus conditional compilation, via cabal.  See 
http://bit.ly/cBDj3Q for more on that one.


I could also cite the habit of Hackage to routinely get more and more 
pedantic, rejecting packages that uploaded fine previously; renaming the 
old exception model to OldException instead of introducing the new one 
with a different name (thus breaking much exception-using code), etc.


My point is not that innovation in this community is bad.  Innovation is 
absolutely good, and I don't seek to slow it down.


But rather, my point is that stability has value too.  If I can't take 
Haskell code written as little as 3 years ago and compile it on today's 
platform without errors, we have a problem.  And there is a significant 
chunk of code that I work with that indeed wouldn't work in this way.


I don't have a magic bullet to suggest here.  But I would first say that 
this is a plea for people that commit to core libraries to please bear 
in mind the implications of what you're doing.  If you change a time 
format string, you're going to break code.  If you introduce new 
instances, you're going to break code.  These are not changes that 
should be made lightly, and if they must be made (I'd say there's a 
stronger case for the time instances than the s/ /T/ change), then the 
version number must be bumped significantly enough to be Cabal-testable.


I say this with a few hats.  One, we use Haskell in business.  Some of 
these are very long-term systems, that are set up once and they do their 
task for years.  Finding that code has become uncompilable here is 
undesirable.


Secondly, I'm a Haskell library developer myself.  I try to maintain 
compatibility with GHC  platform versions dating back at least a few 
years with every release.  Unfortunately, this has become nearly 
impossible due to the number of untestable API changes out there.  That 
means that, despite my intent, I too am contributing to the problem.


Thoughts?

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


Re: [Haskell-cafe] The instability of Haskell libraries

2010-04-23 Thread John Goerzen

Don Stewart wrote:

I'll just quickly mention one factor that contributes:

* In 2.5 years we've gone from 10 libraries on Hackage to 2023 (literally!)

That is a massive API to try to manage, hence the continuing move to
focus on automated QA on Hackage, and automated tools -- no one wants
to have to resolve those dependencies by hand.


Yep, it's massive, and it's exciting.  We seem to have gone from stodgy 
old language to scrappy hot one.  Which isn't a bad thing at all.


Out of those 2023, there are certain libraries where small changes 
impact a lot of people (say base, time, etc.)  I certainly don't expect 
all 2023 to be held to the same standard as base and time.  We certainly 
need to have room in the community for libraries that change rapidly too.


I'd propose a very rough measuring stick: anything in the platform ought 
to be carefully considered for introducing incompatibilities.  Other 
commonly-used libraries, such as HaXML and HDBC, perhaps should fit in 
that criteria as well.


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


Re: [Haskell-cafe] The instability of Haskell libraries

2010-04-23 Thread John Goerzen

Thomas Hartman wrote:

1) Folks, what exactly is the situation with buildbots?


If that's going to happen, then ideally we would have a way to run tests 
as part of the hackage acceptance process.  For instance, the change to 
a time format string wouldn't break anything at compile time, but my 
HDBC test suite sure caught it.


I can see difficulty with this, though, particularly with packages that 
are bindings to C libraries.


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


Re: [Haskell-cafe] Unicode strings and runCommand / runProcess

2010-04-23 Thread John Goerzen

Ivan Lazar Miljenovic wrote:

John Goerzen jgoer...@complete.org writes:

ghci
GHCi, version 6.12.1: http://www.haskell.org/ghc/  :? for help
Loading package ghc-prim ... linking ... done.
Loading package integer-gmp ... linking ... done.
Loading package base ... linking ... done.
Prelude :m System.Process
Prelude System.Process runCommand echo привет
?...@825b


Are you arguing about IO-specific stuff like this, or for all non-ASCII
Strings?



I'm not sure I understand the question.  I consider the behavior in 
System.IO to be well-documented.  The behavior in System.Process is not 
documented at all.  As I said, I'm not certain what the proper answer 
is, but not documenting what happens probably isn't it.


Actually, the behavior of openFile when given a String with characters  
0xFF is also completely undocumented.  I am not sure what it does with 
that.  It should probably be the same as runCommand, whatever it is.


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


Re: [Haskell-cafe] The instability of Haskell libraries

2010-04-23 Thread John Goerzen

David Leimbach wrote:
I think managers expect magic bullets and holy grails... sometimes they 
just end up with holy cow's (or other more interesting 4 letter words) 
instead.


The good news for me, at least, is that *I* am the manager.  (Yep, the 
company is small enough for that.)  Actually, it should be stated that 
Haskell has still been a huge overall win for us, despite this.  I by no 
means am contemplating a switch away from it because of this.


It must be said, too, that our core library, while perhaps less stable 
than Python's, seems to me to be of a much higher quality.  Or perhaps 
I'm jaded after 8 years (!) of working with imaplib.py...


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


Re: [Haskell-cafe] The instability of Haskell libraries

2010-04-23 Thread John Goerzen

Ivan Lazar Miljenovic wrote:

I think the release early, release often slogan is an affect on this
as well: we encourage library writers to release once they have
something that _works_ rather than waiting until it is perfect.  The
fact that we encourage smaller, more modular libraries over large
monolithic ones also affects this.


That is absolutely a good thing for many libraries here.  I'm all in 
favor of low barriers to entry, and took advantage of such when I was 
starting out in this community.  And I thank those many of you that have 
been around longer than I for putting up with my early code ;-)


On the other hand, there are certain libraries that are very 
well-established and so popular that they are viewed by many as pretty 
much part of the language.  Here I think of ones such as old-time or 
time, unix, bytestring, containers, etc.  I think that if release early 
 often is to be practiced with these, then there ought to be a 
separate stable branch that is made widely available, with development 
releases numbered differently (as the Linux kernel used to do) or only 
available via version control.



When considering Haskell vs Python, I wonder if the stability of
Python's libraries is due to their relative maturity in that the
fundamental libraries have had time to settle down.


It is a funny thing, because our fundamental libraries *have* had time 
to settle down, in a sense.  In another sense, I must say that the 
innovations we have seen recently have been sorely needed and are 
unquestionably a good thing.  The new time, exceptions, regex 
improvements, Unicode support in IO, etc. are all things of immediate 
practical benefit.  I guess this is the price of failing to avoid 
success, to borrow Simon's phrase.  And again, not entirely bad.


Incidentally, I think that the introduction of the new time was handled 
very well.  No old code had to change (except perhaps for the .cabal 
file), and yet new development could ignore old-time.


My intent here wasn't to stir up some grand new level of QC.  Just to 
request a bit more forethought before changing APIs.


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


Re: [Haskell-cafe] The instability of Haskell libraries

2010-04-23 Thread John Goerzen

Don Stewart wrote:


Oh, the Platform has very strict standards about APIs,

When a package may be added:


http://trac.haskell.org/haskell-platform/wiki/AddingPackages


That looks like a very solid document.  Does it also apply when 
considering upgrading a package already in the platform to a newer version?


Also, I notice that 
http://haskell.org/haskellwiki/Package_versioning_policy does not 
mention adding new instances, which caused a problem in the past.  I 
would argue that this ought to mandate at least a new A.B.C version, if 
not a new A.B.


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


Re: [Haskell-cafe] Unicode strings and runCommand / runProcess

2010-04-23 Thread John Goerzen

Khudyakov Alexey wrote:

Actually, the behavior of openFile when given a String with characters 
0xFF is also completely undocumented.  I am not sure what it does with
that.  It should probably be the same as runCommand, whatever it is.

Under unices file names are just array of bytes. There is no notion of encoding 
at all. It's just matter of interpretation of that array. 


Quite right.  One must be able to pass binary strings, which contain 
anything except \0 and '/' to openFile.  The same goes for runCommand. 
I am uncomfortable, for this reason, with saying that runCommand ought 
to re-encode in the system locale while openFile doesn't.  It is 
preferable to drop characters than to drop the ability to pass arbitrary 
binary data.


So I am not sure I agree with your stance in 
http://hackage.haskell.org/trac/ghc/ticket/4006


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


Re: [Haskell-cafe] The instability of Haskell libraries

2010-04-23 Thread John Goerzen

David Menendez wrote:

On Fri, Apr 23, 2010 at 10:11 PM, John Goerzen jgoer...@complete.org wrote:

Don Stewart wrote:

Oh, the Platform has very strict standards about APIs,

When a package may be added:
   http://trac.haskell.org/haskell-platform/wiki/AddingPackages

That looks like a very solid document.  Does it also apply when considering
upgrading a package already in the platform to a newer version?

Also, I notice that http://haskell.org/haskellwiki/Package_versioning_policy
does not mention adding new instances, which caused a problem in the past.
 I would argue that this ought to mandate at least a new A.B.C version, if
not a new A.B.


Adding or removing instances requires a new major version. See section 2:

| If any entity was removed, or the types of any entities or the definitions of
| datatypes or classes were changed, or instances were added or removed,
| then the new A.B must be greater than the previous A.B.



Ah, sorry.  Read it too quickly I guess.
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Adopting MissingPy?

2010-04-21 Thread John Goerzen

Hi folks,

MissingPy is a library I wrote a little while back that allows you to 
call Python code from Haskell.  It's on Hackage and, as far as I know, 
still works.


Trouble is, the need I used to have for it is gone. So I no longer use 
it myself for anything, and thus it is starting to bitrot.


Would anyone like to take over maintenance of this project?

Thanks,

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


Re: [Haskell-cafe] HDBC-ODBC and SqlValues

2010-04-08 Thread John Goerzen
Tim Docker wrote:
 Jason:
 
 Thanks for the reply.
 
 I suspect the solution is to correctly tell Haskell what type you
 expect and then hopefully HDBC will do the conversion.  For example,
 using fromSql:
 http://software.complete.org/static/hdbc/doc/Database-HDBC.html#v%
 3AfromSql
 
 Yes. I can use fromSql to convert the result back to an appropriate
 numerical type. But internally the numeric data has still been converted
 to an intermediate string representation. I'm wondering if this is
 intentional, and whether it matters.

Yes and no, in that order.

A ByteString is a pretty universal holder for various types of data.  As
someone else pointed out, at query time, we don't really have access to
what type you will eventually want to use it as, and supporting the vast
number of different ways to get things out of databases -- with the
corresponding complexities of how a database driver can convert between
them -- was just not worth it.

It is generally assumed that the end user will be using fromSql anyhow,
so it is not particularly relevant if it's a SqlByteString or a
SqlInteger internally.

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


Re: [Haskell-cafe] HDBC-ODBC and SqlValues

2010-04-08 Thread John Goerzen

Tim Docker wrote:

*Main fmap (fromSql.head.head) $ quickQuery c select getdate() [] ::
IO Data.Time.Clock.UTCTime
2010-04-09 09:59:20.67 UTC
*Main fmap (fromSql.head.head) $ quickQuery c select getdate() [] ::
IO Data.Time.LocalTime
2010-04-09 09:59:26.313
*Main fmap (fromSql.head.head) $ quickQuery c select getdate() [] ::
IO System.Time.CalendarTime
*** Exception: Convertible: error converting source data SqlString
2010-04-09 09:59:37.460 of type SqlValue to type


That is to be expected.  You are converting data from the underlying 
database that does not contain timezone information.  Thus it is not 
possible to populate ctTZ in CalendarTime.



Data.Time.LocalTime.LocalTime.ZonedTime: Cannot parse using default
format string %Y-%m-%d %T%Q %z
*Main fmap (fromSql.head.head) $ quickQuery c select getdate() [] ::
IO System.Time.ClockTime
*** Exception: Convertible: error converting source data SqlString
2010-04-09 09:59:49.940 of type SqlValue to type Integer: Cannot read
source value as dest type


And here you don't have something in seconds-since-epoch format.  What 
you have is an unzoned date and time.  Therefore it makes sense that you 
can convert it to a LocalTime.  It does not have enough information to 
make it into a CalendarTime because it lacks a zone.  It also isn't in 
seconds-since-epoch format, which is what a ClockTime is.


The conversions to UTCTime and LocalTime work because they do not 
require a timezone to be present in the input data.


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


[Haskell-cafe] Re: Weird behaviour with positional parameters in HDBC-mysql

2010-04-07 Thread John Goerzen

Martijn van Steenbergen wrote:


Is this a problem in HDBC or in HDBC-mysql?


Smells to me like a bug in HDBC-mysql.  However, it is possible that the 
bug lies in the C MySQL library itself.


To help isolate, it would be good to try your program:

 * with HDBC-postgresql
 * with HDBC-sqlite3
 * with HDBC-ODBC and the MySQL driver

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


Re: [Haskell-cafe] Where are the haskell elders?

2010-04-01 Thread John Goerzen
Ivan Miljenovic wrote:
 2010/3/30 Don Stewart d...@galois.com:
 I notice that posts from the Haskell elders are pretty rare now. Only
 every now and then we hear from them.

 How come?
 Because there is too much noise on this list, Günther
 
 And they have better things to do than answer stupid questions and get
 involved in petty discussions.
 

Or perhaps people with an overly-condescending attitude are making this
list a less friendly place?

Personally, I used to highly commend haskell-cafe for being such a
friendly place.  After catching up on it after a bit of a vacation, I'm
not so sure about that anymore.  Perhaps that is a price of failing to
avoid success, but I wish it weren't.

Couldn't you have said that in a bit of a more polite way?  Perhaps
without spewing it to thousands of readers while you're at it?

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


[Haskell-cafe] MissingH dropped QuickCheck dep

2010-02-12 Thread John Goerzen
On Fri, Feb 12, 2010 at 08:45:09AM -0800, John MacFarlane wrote:
 +++ thomas hartman [Feb 11 10 21:07 ]:
  gitit on hackage is still blocked because of dependency on missingh,
  which depends on qc1. Not an easy fix -- I couldn't figure out how to
  migrate testpack to qc2.
  
  However, missingh dependency was removed from gitit head
  
  http://github.com/jgm/gitit
  
  so that's good.
 
 No, gitit head still depends on MissingH, via ConfigFile.
 
 I imagine John will update MissingH to use QuickCheck2 soon...

Hey guys, I took a look at MissingH and there was no need for the main
library to depend on QuickCheck in the first place.  It was only
needed by the tests.  So I've uploaded a new MissingH 1.1.0.2 to
Hackage that drops that dep.

That ought to solve it for you.

-- John

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


[Haskell-cafe] Re: MissingH dropped QuickCheck dep

2010-02-12 Thread John Goerzen
Don Stewart wrote:
 Excellent!
 
 Would it be possible to disable the runtests executable by default?
 Enable it only with a conditional?

It's been that way for quite some time now:

Executable runtests
  Buildable: False

heh, and I didn't even add a flag for it yet like I have with HDBC.
Guess I ought to do that so a person can build tests more easily if they
wish.

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


Re: [Haskell-cafe] Supporting GHC 6.10 and 6.12 in HDBC-postgresql Setup.hs

2010-01-27 Thread John Goerzen
Neil Mitchell wrote:
 The other HDBC problem I have is various dependencies relying on QC1.

 The next HP will ship with QC 2.1 (in coming weeks), so it might be a
 good time for people to start migrating, since that will be the only
 version of QC on many distros.
 
 I would strongly suggest moving to QC 2 for other reasons as well. It
 does substantially better at searching the random space, to the extent
 where several of my properties pass under QC 1 but fail under QC 2.
 It's a much better testing tool.

I will be making that change once it gets into haskell-platform (and
once I have the time).

My more urgent problem, though, is maintaining Cabal compatibility with
6.10 and 6.12.

-- John

 
 Thanks, Neil
 

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


[Haskell-cafe] Supporting GHC 6.10 and 6.12 in HDBC-postgresql Setup.hs

2010-01-26 Thread John Goerzen
Hi folks,

I've gotten some reports (see below) of issues with building
HDBC-postgresql on GHC 6.12.  Its Setup.hs file [1] is the culprit.  The
problem is that AnyVersion needs to be removed to work with Cabal in GHC
6.12.

But I still want to support older Cabal.

Following the directions in the Cabal manual, I tried:

#if MIN_VERSION_Cabal(1,8,0)
 pgconfigProgram (withPrograms lbi)
#else
 pgconfigProgram AnyVersion (withPrograms lbi)
#endif

While of course adding the needed bits to invoke CPP.  This didn't
resolve it; apparently Cabal doesn't define macros for use in Setup.hs,
only for use in the application.

There also seems to be no conditional for use in the .cabal file to
resolve this.

I could check the GHC version, but that doesn't necessarily correspond
to Cabal version.

Any ideas?

-- John

[1]
http://git.complete.org/hdbc-postgresql?a=blob;f=Setup.hs;h=0656cb41adc814de8542b6f28040e131ae86be3c;hb=HEAD
---BeginMessage---
Hello John,

I don't know if you're aware but HDBC-postgresql is failing to build on 
hackage. I think this is because the requireProgram function used in Setup.hs 
has changed between cabal 1.6 and cabal 1.7 (the version parameter has been 
removed).

It seems to build fine if you simply remove the AnyVersion argument in Setup.hs 
line 39, apparently this is the only thing stopping it from building on cabal 
1.8/ghc 6.12, I haven't checked cabal 1.7/ghc 6.10. I don't know what changes 
to the versions in the cabal file should go with this, if just adding cabal = 
1.7 is correct or not.

Will you be able to upload a fixed version to hackage in the near future? It 
would be handy for me so that my project's haddock docs appear there on hackage 
(my project is hssqlppp). It's not particularly urgent, so please don't rush on 
my account.

Thanks for all your great contributions on hackage, Real World Haskell and 
elsewhere,
Jake Wheat

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


[Haskell-cafe] Adopting hpodder?

2010-01-25 Thread John Goerzen
Hi folks,

I wrote hpodder a little while back.  I no longer listen to podcasts at
all (blame my Kindle for that).  Is anyone here interested in adopting
it and giving it some needed care?

Thanks,

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


Re: [Haskell-cafe] Trouble installing HDBC 2.1.1 with ghc 6.10.4

2009-11-16 Thread John Goerzen
Colin Paul Adams wrote:
 Is this connected with the in-and-out status of the time library in
 the GHC 6.10.x series?
 
 Is there a work-around?

Using the current HDBC (2.2.1) would fix it for you.

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


[Haskell-cafe] Time Typeable Instances

2009-10-13 Thread John Goerzen
Hugo Gomes wrote:
 The Glorious Glasgow Haskell Compilation System, version 6.10.4
 with old-time-1.0.0.2 and time-1.1.2.4
 
 This is a standard haskell platform on a windows xp. Cabal install
 didn't work complaining about missing instances of typeable for posix
 time and other datatypes, yet, after removing the macros (thus, adding
 those instances), hdbc and convertible compiled and installed fine. 
 
 Removing the macros might be a bit overkill, probably finetuning them so
 that they add only the necessary instances for typeable in ghc  610
 might be a better solution.

I'm going to CC haskell-cafe on this because I am confused.

Hugo, can you confirm what version of convertible you have?

Back on May 21, I started a thread [1] on haskell-cafe complaining that
GHC 6.10.3 included a newer time that included instances of Typeable for
NominalDiffTime and UTCTime.  This broke my code, which had manually
defined instances for these types, as they were needed.  Things got
complicated, as only time's minor version number got incremented
(x.x.x.Y) [2].  Cabal can't test against that version number.

I wanted my code to work with old and new versions of GHC.  Since
testing against the version of time was impossible, I did the next best
thing: tested against the version of GHC.

#if __GLASGOW_HASKELL__ = 610
-- instances added in GHC 6.10.3
#else
instance Typeable NominalDiffTime where
typeOf _ = mkTypeName NominalDiffTime

instance Typeable UTCTime where
typeOf _ = mkTypeName UTCTime
#endif

Also, in the .cabal, there is a build-depends on time=1.1.2.4.

Now, that would break for GHC 6.10.1 and 6.10.2 users, but will work for
6.10.3 and above, or 6.8 and below.  Or so I thought.

Now I'm getting complaints from people using 6.10.4 saying that there
are now missing instances of Typeable with time 1.1.2.4.

1) Did the Typeable instances get dropped again from time?
2) What exactly should I do so this library compiles on GHC 6.8 and 6.10.x?

I'm looking at the darcs repo for time and don't see the instances ever
getting dropped.

[1] http://osdir.com/ml/haskell-cafe@haskell.org/2009-05/msg00982.html
[2] http://osdir.com/ml/haskell-cafe@haskell.org/2009-05/msg00985.html


 later addendum 

so it appears that what's happening here is that GHC 6.10.3 extralibs
included time 1.1.3, but then haskell-platform standardized on 1.1.2.4.
 This is pretty annoying -- that haskell-platform would standardize on a
version older than what shipped with a GHC release -- but I guess I can
work around it by restricting my build-dep to be time  1.1.3 and
re-adding the instances.

Does this sound right?

 
 
 On Tue, Oct 13, 2009 at 2:51 AM, John Goerzen jgoer...@complete.org
 mailto:jgoer...@complete.org wrote:
 
 Hugo Gomes wrote:
  Hi,
 
  convertible and hdbc packages fail to compile in my standard
 instalation
  of the haskell platform. I think this has to do with those if ghc =
  610 macros on the typeable instances for some datatypes. I
 removed them
  and now they work fine...
 
 
 
 
 
 What version of GHC and time do you have?
 
 -- John
 
 

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


Re: [Haskell-cafe] HDBC PostgreSQL

2009-10-09 Thread John Goerzen
Patrick Brannan wrote:
 Prelude module HDBC HDBC.PostgreSQL
 
 Now I would think that the line Loading package
 HDBC-postgresql-2.1.0.0 ... linking ... done. means that the module
 is installed correctly, but I still can't execute the :module
 statement.
 
 Does anyone have any ideas about where I should start? It's probably
 something stupid, but I'm a little worn out on searching.

That's because you're confusing package names with module names.

I suspect you meant

:m Database.HDBC Database.HDBC.PostgreSQL

The API docs on Hackage will list the modules that any package provides.

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


Re: Fwd: [Haskell-cafe] suggestion for hslogger

2009-09-30 Thread John Goerzen
If you want to send me a patch that makes it an option (not mandatory),
I would be happy to apply it.

-- John

Antoine Latter wrote:
 Forwarding on to the maintainer, in case he's not on the list.
 
 
 -- Forwarded message --
 From: Sean McLaughlin sean...@gmail.com
 Date: Tue, Sep 29, 2009 at 1:31 PM
 Subject: [Haskell-cafe] suggestion for hslogger
 To: haskell-cafe@haskell.org
 
 
 Hello,
   I have a program that does a lot of unicode manipulation.  I'd like
 to use hslogger to log various operations.
 However, since hslogger uses System.IO.putX, the unicode comes out
 mangled.  I hacked the source to
 use System.IO.UTF8 instead, but it would be nice if that was an option
 so I don't have to rehack the code
 whenever there is a new release.
 Thanks!
 Sean
 ___
 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: Fwd: [Haskell-cafe] suggestion for hslogger

2009-09-30 Thread John Goerzen
Duncan Coutts wrote:
 On Wed, 2009-09-30 at 08:36 -0500, John Goerzen wrote:
 If you want to send me a patch that makes it an option (not mandatory),
 I would be happy to apply it.
 
 When reviewing it do consider the new Unicode IO library.
 
 http://ghcmutterings.wordpress.com/2009/09/30/heads-up-what-you-need-to-know-about-unicode-io-in-ghc-6-12-1/
 
 One option is to do nothing and just wait.

That is probably the best.

-- John

 
 Duncan
 
 

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


Re: [Haskell-cafe] haskelldb + sqlite problem.

2009-06-22 Thread John Goerzen
Magicloud Magiclouds wrote:
 Hi,
   I am using haskelldb and haskelldb-hdbc-sqlite3. Well, I finally got
 the source compiled and ran, I got this error:
 App: user error (SQL error: SqlError {seState = , seNativeError =
 21, seErrorMsg = prepare 74: SELECT subject,\n   timestamp\nFROM
 notes as T1\nORDER BY timestamp DESC: library routine called out of
 sequence})
   Any clue what I should check? Thanks.

At the HDBC level, I would say:

I suspect that you have used a function that returns results lazily, but
haven't completely read them before calling back into the database with
something else.  As an example, you should probably use quickQuery'
instead of quickQuery, unless you are fully prepared to accept the
consequences of reading data lazily from a database.

I am not very familiar with HaskellDB, and can't really comment on what
it's doing under the hood.  If it is returning results to you lazily,
make sure you have completely consumed them before sending more queries
to the database.

If you can post some example code, it would likely help.

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


Re: [Haskell-cafe] Re: haskelldb + sqlite problem.

2009-06-22 Thread John Goerzen
GüŸnther Schmidt wrote:
 Hi Cloud,
 
 this often occurs when the path to the database includes a non-ascii 
 character.
 
 In my dev environment, the path to the database deliberately contains an 
 umlaut and the original code base of hdbc.sqlite3 from John Goerzen, 
 version 2.0  version 2.1 thus does not work.

This is conflating many issues.

I do recall some discussion about data within a database; I don't recall
one about the filename of it, which would certainly be a separate
discussion.  I can see why a connectRaw or some such function could be
useful if you want to pass a raw binary string as the file path to
Sqlite3.  (I don't think any other DB would have a use for such a thing).


 John Goerzen, the author of HDBC has considerably rewritten some parts 
 of his hdbc package to use utf8-string wrapping, which includes wrapping 
   the connection string, and in my case caused considerable problems, it 
 just wouldn't work. So my solution was to rollback all these changes 
 where he used the utf8-wrapping, which was quite a lot of work. I did 

And unnecessary work at that, if all you cared about was the filename.

I see your point on the filename, and tweaking that would have been a
one-line fix for you.

The mess we had before was this huge cloud of **UNDEFINED BEHAVIOR**
when dealing with anything other than 7-bit ASCII.  Databases could have
some encodings, systems could have encodings, and it was all a huge fiasco.

So with HDBC 2, what we have is:

 * If you want to communicate with the database in a raw manner, use
ByteStrings.  If you want a String out of it, convert it yourself.

 * If you want to use Strings to communicate with the databases, these
will automatically be converted to the appropriate Unicode
representation by the library.  For all current database backends, that
means converting them to a UTF-8 CStringLen type of thing, and back.

 Anyway what you can do, for now, is to put your sqlite3 database file 
 into a location where the path contains no non-ascii characters, that 
 should fix the problem.

His problem is not caused by non-ASCII characters.

 You may experience other, utf8-wrapping related problems, for instance 
 when you want to insert non-ascii strings into varchar columns. They may 
 not come back as you put them in.

They will, unless you are doing something weird like putting Latin1
8-bit text into a String and passing it to HDBC as a String, when the
documentation specifically states that Strings are expected to be in the
Unicode space.  As I recall, that is specifically what you were doing.

That doesn't mean I haven't provided an outlet for you to do deal with
things in the Latin1 space (see the ByteString discussion above.)

But in truth, HDBC is not a character set conversion library, nor should
it be.  If you have more complex needs than Unicode Strings, use one of
the many quality encoding libraries available for Haskell, and combine
it with the ByteString features in HDBC.

Every popular database that I am aware of can either speak UTF-8
directly, or convert transparently to and from it.

So, to summarize:

1) This is not the original poster's problem.

2) HDBC 2 is simpler than HDBC 1, and actually defines behavior in terms
of character sets rather than leaving it completely undefined.

3) HDBC 2 standardizes character sets around UTF-8, the most common
global standard, and structures its API in a way that this is
transparent when you want it to be, and available for manual processing
when you want that.

4) Nothing requires you to use UTF-8, which is why the ByteString API is
there.

5) A one-line patch would have fixed your filename connection issue.

6) If memory serves, your not getting things back is because you are
storing non-Unicode data in your Strings, and then using an improper API
to store it.

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


Re: [Haskell-cafe] Re: haskelldb + sqlite problem.

2009-06-22 Thread John Goerzen
John Goerzen wrote:
 I do recall some discussion about data within a database; I don't recall
 one about the filename of it, which would certainly be a separate
 discussion.  I can see why a connectRaw or some such function could be

I have just pushed a patch to my git repo that adds connectSqlite3Raw to
help in these cases.

You can grab the diff directly here:

http://git.complete.org/hdbc-sqlite3?a=commitdiff_plain;h=0ef5df694d74cfaea7da3fcfc97037411d3f13bb

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


Re: [Haskell-cafe] Re: haskelldb + sqlite problem.

2009-06-22 Thread John Goerzen
GüŸnther Schmidt wrote:
 Hi John,
 
 let me first of all apologize, I didn't mean to criticize you, I'm sure 
 you had good reasons for those changes, I'm merely mean to state how 
 they did affect me after switching to HDBC 2.1.

No, I completely understand and I'm not offended; but I didn't want
people reading this message to get the wrong idea about the state of
Unicode support in HBDC.

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


Re: [Haskell-cafe] Use MySQL from Haskell

2009-06-19 Thread John Goerzen
Maciej Podgurski wrote:
 Building convertible-1.0.5...

There was unfortunately an API change in GHC 6.10.3 that could not be
worked around.  Either upgrade to 6.10.3 or use an older version of
convertible.

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


[Haskell-cafe] Re: HSH and IO ()

2009-06-13 Thread John Goerzen
Dimitry Golubovsky wrote:
 John,
 
 Thanks for the reply.
 
 In this case, would the body of my function run in a separate thread
 via forkProcess (that's what is needed, maybe I didn't make it clear)?

No; at least not automatically.  The idea is that a function that is
Channel - IO Channel should be very similar in concept to a String -
String - processing its input lazily.

 In my previous project, I had to do like this (probably not very
 portable, at least requires System.Posix):

You are aware that HSH has built-in support for executing external
commands, right?

What is hssfigMain?  Is it calling some other program or is it part of
the current process?  I would suggest that the appropriate idea is to
make hsffigMain be some other executable.  Then you could just:

runIO $ (hsffigMain, [args, args, ...]) -|-
(fromJust $ gccPath dopt, [-E, -dD, ...])

 where hscpid corresponds to a process that runs a Haskell function
 (hsffigMain :: a - b - c - IO ()) defined within the same program,
 and gccpid runs an external program (gcc), and they are piped
 together. I am trying to avoid writing this mess using HSH.

OK, so I should have read more before starting to reply.  But why are
you writing to me about HSH if you're trying to *avoid* HSH?  I'm confused.

 I'm just trying to find out whether this was already done. If not,
 what is the best way to write the above to be integrated into HSH (I'd
 be glad to contribute).

Integraing hsffigMain into HSH directly will be difficult because it
apparently already has its notions about where its input and output come
from; the fact that its return type is IO () implies that its output
either goes to stdout or to a file.  This type of function cannot be
generalized to pipes, because you can only dup2() your stdout once.
(You couldn't have two functions like hsffigMain in your pipeline).

Your best bet is to make this a separate executable.

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


Re: [Haskell-cafe] Re: HSH and IO ()

2009-06-13 Thread John Goerzen
On Sat, Jun 13, 2009 at 05:06:41PM -0700, Jason Dagit wrote:
 On Sat, Jun 13, 2009 at 4:01 PM, John Goerzen jgoer...@complete.org wrote:
 
  Dimitry Golubovsky wrote:
 
   where hscpid corresponds to a process that runs a Haskell function
   (hsffigMain :: a - b - c - IO ()) defined within the same program,
   and gccpid runs an external program (gcc), and they are piped
   together. I am trying to avoid writing this mess using HSH.
 
  OK, so I should have read more before starting to reply.  But why are
  you writing to me about HSH if you're trying to *avoid* HSH?  I'm confused.
 
 
 I think Dimitry meant, I'm trying to avoid writing this mess *by* using HSH
 instead.
 
 At least, that's how I read it.

Ah, that makes more sense.  Sorry for the misparsing.

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


[Haskell-cafe] Re: HSH and IO ()

2009-06-13 Thread John Goerzen
Dimitry Golubovsky wrote:

 I'll try to write a wrapper for a forked process inside a Channel -
 IO Channel typed function.

Your best bet would be to start with these instances in HSH.Command:

instance ShellCommand (String, [String]) where
instance ShellCommand String where

and the implementation of genericCommand, which they both call.

It is really not that difficult of an implementation, and as of GHC
6.10, no longer even requires the specialized POSIX items.

The reason I have two bodies for genericCommand is that if the input
channel is a Handle, I can pass it directly as stdin to the child
process; otherwise, it is necessary to use chanToHandle to zap it over
to stdin.

Now, with what you're trying to do, you will probably not be able to get
away without using the POSIX stuff though, since you have to dup2()
stdin/stdout.

I still recommend splitting this into multiple executables.  With your
approach, the stdin and stdout of your main executable will be messed up
forever.  This can and does lead to unforseen consequences.

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


[Haskell-cafe] Re: HSH and IO ()

2009-06-12 Thread John Goerzen
Dimitry Golubovsky wrote:
 John  all,
 
 I use HSH in my project where several external programs and Haskell
 functions need to be piped together: HSH is of great help here.
 
 I however came across the situation when one of pipe-connected
 functions has signature IO (), yet it reads from stdin* and writes to
 stdout.
 
 The documentation mentions instance ShellCommand (Handle - Handle -
 IO ()) which could be of some help, but in the latest version of HSH
 on Hackage this instance is commented out.
 
 What was the reason of doing that? Is this to be expected in the
 upcoming versions?

Yes; that's due to the new more flexible way of sending data between
processes in HSH -- the Channel.

You can replace it with a function that can take any Channel, and
produce a result as a Channel of one particular sort.  In particular,
this instance:

instance ShellCommand (Channel - IO Channel) where

is the direct replacement for what you were doing.

A Channel is generally a String, a lazy ByteString, or a Handle.

There are helper functions in HSH.Channel to deal with these:
chanAsString, chanAsBSL, and chanToHandle.  You can think of the first
two as similar to hGetContents.  The last will write the channel out
literally to a passed-along handle.

So, let's say that you wanted to process input as a String, and before
you were given a Handle that you used hGetContents on.  Now, you will
get a Channel, on which you will call chanAsString.  It will convert
whatever type of Channel you were handed into a String, lazily.

Does that make sense?
___
Haskell-Cafe mailing list
Haskell-Cafe@haskell.org
http://www.haskell.org/mailman/listinfo/haskell-cafe


[Haskell-cafe] Static link to packages on Hackage?

2009-06-04 Thread John Goerzen
Hi,

I'd like to be able to put a static link to the Haddock docs for the
current version of various packages on my homepage.  Right now, I can't
find any such URL; they all look like:

http://hackage.haskell.org/packages/archive/HSH/2.0.0/doc/html/HSH.html

I'd like if there could be something like:

http://hackage.haskell.org/packages/archive/HSH/latest/doc/html/HSH.html

Incidentally, you can click on this latest URL but it doesn't go to
the correct version.

I can't just link to the package page either, because sometimes it won't
have docs (such as shortly after I've uploaded a new version).

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


Re: [Haskell-cafe] Static link to packages on Hackage?

2009-06-04 Thread John Goerzen
Thomas ten Cate wrote:
 http://hackage.haskell.org/packages/archive/HSH/latest/doc/html/HSH.html
 does take me to a page that says
 HSH-2.0.0: Library to mix shell scripting with Haskell programs
 in the blue bar at the top.
 
 Maybe some kind of cache? Did you try flushing your browser cache and
 refreshing? Am I missing something?

Weird.  I just now hit reload, and it came up to the correct version.  I
wonder if perhaps it didn't get updated at the same time the docs did?

 
 Thomas
 
 On Thu, Jun 4, 2009 at 15:20, John Goerzenjgoer...@complete.org wrote:
 Hi,

 I'd like to be able to put a static link to the Haddock docs for the
 current version of various packages on my homepage.  Right now, I can't
 find any such URL; they all look like:

 http://hackage.haskell.org/packages/archive/HSH/2.0.0/doc/html/HSH.html

 I'd like if there could be something like:

 http://hackage.haskell.org/packages/archive/HSH/latest/doc/html/HSH.html

 Incidentally, you can click on this latest URL but it doesn't go to
 the correct version.

 I can't just link to the package page either, because sometimes it won't
 have docs (such as shortly after I've uploaded a new version).

 Ideas?
 ___
 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] ANN: HSH 2.0.0

2009-06-03 Thread John Goerzen
Hi,

I'm pleased to announce the release of version 2.0.0 of HSH, the
Haskell shell scripting library.

This version features a complete rewrite of the core.  Since
System.Process has finally become capable enough to be the low-level
of HSH, HSH has been reimplemented in terms of it.  This has produced
a dramatic reduction in code size and complexity.  It also gains
cross-platform support; HSH now works on Windows.  Finally, the API
is both simpler and more flexible.

The 180-test suite for HSH continues to run and pass with only minor
tweaks for the new API.

Optional support for setting environment variables on commands to be run has
been added as well.  It will stay out of your way unless you need it,
in which case it is easy.

As a reminder, HSH lets you easily set up shell command pipelines.
You can also pipe data between Haskell functions and shell commands
with complete ease.  The package also provides Haskell versions of a
number of familiar shell primitives to help you get up and running
quickly.

HSH 2.0.0 has been uploaded to Hackage.

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


Re: [Haskell-cafe] Introducing Instances in GHC point releases

2009-05-22 Thread John Goerzen
Don Stewart wrote:
 duncan.coutts:
 What we're currently missing is a PVP checker: a tool to compare APIs of
 package versions and check that it is following the PVP. Ideally, we
 will have packages opt-in to follow the PVP for those packages that do
 opt-in we have the PVP enforced on hackage using the checker tool. Since
 the HP is almost certainly going to require packages to follow the PVP
 then this should eliminate this class of mistakes. But it does need the
 tool, and nobody is working on that at the moment.
 
 If I recall correct, CosmicRay wrote just such a thing (or similar to
 it) a while ago.
 
 John?

Nope, that wasn't me.  Maybe the other John?

 
 -- Don
 

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


Re: [Haskell-cafe] Introducing Instances in GHC point releases

2009-05-22 Thread John Goerzen
Henning Thielemann wrote:
 John Goerzen schrieb:
 So this is annoying (CCing -cafe)

 I need NominalDiffTime and UTCTime to have Typeable instances.  In
 6.10.1, they didn't ship with them out of the box, so I added them.
 Apparently, in 6.10.3, they DO ship with those instances out of the box.

 Annoyingly, that means that my code breaks on 6.10.3.
 
 After having conflicting instances several times with some types in the
 past, I came to the conclusion that I should never define orphan
 instances. Can you restrict your package to 6.10.3 where an official
 instance is available?
 
 http://www.haskell.org/haskellwiki/Orphan_instance
 

I didn't care about presenting the instance to people using my library,
but the instance was necessary within the library itself, and led to the
compilation error.

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


Re: [Haskell-cafe] ANN: feed2twitter 0.2 hackage2twitter 0.2.1

2009-05-21 Thread John Goerzen
On Thu, May 21, 2009 at 09:10:23PM +0200, Tom Lokhorst wrote:
 Oh, and while we're talking off topic.
 I don't know who's in charge of this, but I think it would be nice to
 have urls like: http://hackage.haskell.org/feed2twitter

YES!

Also a /package/doc link.  So we could have a static link that would
always go the latest version of the API docs for a given package.

-- John

 
 It would allow me to type in a url from memory instead of having to
 copy-paste it. As well as not requiring a url-shortener on Twitter.
 This could be done with something like Apache's mod-rewrite.
 
 - Tom
 
 On Thu, May 21, 2009 at 8:59 PM, John Van Enk vane...@gmail.com wrote:
  A bit off topic, but what's the chance we can get the Hackage RSS feed to
  include some more information about the package? I'd like to see at least
  the description, but it might be nice to see things like dependencies and
  home pages.
 
  /jve
  On Thu, May 21, 2009 at 2:55 PM, Tom Lokhorst t...@lokhorst.eu wrote:
 
  To all the cool kids using the Twitter (and to anyone else):
 
  I'm happy to announce the first release of feed2twitter.
  Build on top of the excellent feed and hs-twitter packages,
  feed2twitter sends posts from a news feed to Twitter.
 
  The hackage2twitter executable is build on top of the feed2twitter
  library. It `tweets' the releases of new Hackage-packages.
  In the 3 days it has been running, it has already posted 70+ releases:
  http://twitter.com/Hackage
 
  - Tom Lokhorst
 
  http://hackage.haskell.org/cgi-bin/hackage-scripts/package/feed2twitter
  http://hackage.haskell.org/cgi-bin/hackage-scripts/package/hackage2twitter
  ___
  Haskell-Cafe mailing list
  Haskell-Cafe@haskell.org
  http://www.haskell.org/mailman/listinfo/haskell-cafe
 
 
 
  --
  /jve
 
 ___
 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] Introducing Instances in GHC point releases

2009-05-21 Thread John Goerzen
So this is annoying (CCing -cafe)

I need NominalDiffTime and UTCTime to have Typeable instances.  In
6.10.1, they didn't ship with them out of the box, so I added them.
Apparently, in 6.10.3, they DO ship with those instances out of the box.

Annoyingly, that means that my code breaks on 6.10.3.

Even more annoyingly, __GLASGOW_HASKELL__ is still 610, so I can't even
work around this via cpphs.  There appears to be no way to make code
that requires those Typeable instances work with both 6.10.1 and 6.10.3.

Yet another reason to avoid API incompatibilities in point releases.

Does anybody have an idea on the best way to handle this?

-- John

Don Stewart wrote:
 convertible appears broken with 6.10.3. Any thoughts?
 
 Writing new package config file... done.
 Downloading convertible-1.0.1...
 Configuring convertible-1.0.1...
 Preprocessing library convertible-1.0.1...
 Preprocessing executables for convertible-1.0.1...
 Building convertible-1.0.1...
 [1 of 8] Compiling Data.Convertible.Base ( Data/Convertible/Base.hs, 
 dist/build/Data/Convertible/Base.o )
 [2 of 8] Compiling Data.Convertible.Utils ( Data/Convertible/Utils.hs, 
 dist/build/Data/Convertible/Utils.o )
 [3 of 8] Compiling Data.Convertible.Instances.Map ( 
 Data/Convertible/Instances/Map.hs, 
 dist/build/Data/Convertible/Instances/Map.o )
 [4 of 8] Compiling Data.Convertible.Instances.Num ( 
 Data/Convertible/Instances/Num.hs, 
 dist/build/Data/Convertible/Instances/Num.o )
 [5 of 8] Compiling Data.Convertible.Instances.C ( 
 Data/Convertible/Instances/C.hs, dist/build/Data/Convertible/Instances/C.o )
 [6 of 8] Compiling Data.Convertible.Instances.Time ( 
 Data/Convertible/Instances/Time.hs, 
 dist/build/Data/Convertible/Instances/Time.o )
 
 Data/Convertible/Instances/Time.hs:61:9:
 Duplicate instance declarations:
   instance Typeable NominalDiffTime
 -- Defined at Data/Convertible/Instances/Time.hs:61:9-32
   instance Typeable NominalDiffTime
 -- Defined in time-1.1.3:Data.Time.Clock.UTC
 
 Data/Convertible/Instances/Time.hs:64:9:
 Duplicate instance declarations:
   instance Typeable UTCTime
 -- Defined at Data/Convertible/Instances/Time.hs:64:9-24
   instance Typeable UTCTime
 -- Defined in time-1.1.3:Data.Time.Clock.UTC
 cabal: Error: some packages failed to install:
 HDBC-2.1.0 depends on convertible-1.0.1 which failed to install.
 convertible-1.0.1 failed during the building phase. The exception was:
 
 

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


Re: [Haskell-cafe] Introducing Instances in GHC point releases

2009-05-21 Thread John Goerzen
Duncan Coutts wrote:
 On Thu, 2009-05-21 at 15:22 -0700, Alexander Dunlap wrote:
 Since those types come out of the time library, and that library's
 version *has* been bumped (I assume), couldn't you use Cabal to
 condition on the version of the time library to determine whether or
 not to have CPP set a -DTYPEABLE_IN_TIME flag, and then #ifdef out
 your versions of the instances?
 
 I was about to suggest this:
 
 #if MIN_VERSION_time(1,1,2)
 ...
 #endif

That would be slick.  I'll give that a whirl.  What version of Cabal
does GHC 6.8 come from, and where can I read about the above feature?  I
imagine I may have to wrap the above in a __GLASGOW_HASKELL__ test for
GHC 6.8 or something.

Though if *cabal* and not GHC generates it, isn't that a bit hurting to
my portability?  (Can't just ghc --make with it, or ghci on it directly
anymore, etc.)

May be a needed tradeoff though.

 
 because Cabal 1.6+ generates these cpp macros for you. Note that relying
 on the value of __GLASGOW_HASKELL__ would be wrong because the version
 of the time library is not directly related to the version of ghc.

Yeah, but when you've got nothing else to go on, it sometimes works in a
pinch.

 However, I note that all the recent versions of time are 1.1.2.x which
 means it didn't bump the API version when it added the instances. 

Ashley, I'll forgive you this time ;-)

I guess my larger point is just a plea to the community: please be
really careful about what you do to GHC in point releases.  This is not
the first issue that has screwed me in the GHC 6.10.x point releases.

GHC (and the community) used to be really good about this.  Is there
something causing a regression here, or is it my imagination?


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


Re: [Haskell-cafe] Trying to contact authors of Real World Haskell?

2009-05-07 Thread John Goerzen
On Thu, May 07, 2009 at 12:18:47PM -0500, Itsme (Sophie) wrote:
 I could not find any contact info for Brian O'Sullivan, Don Stewart, or John
 Goerzen on their book site. Any pointers to how I might locate any of them
 much appreciated.

This post seems to have worked out reasonably well for you :-)

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


Re: [Haskell-cafe] Trying to contact authors of Real WorldHaskell?

2009-05-07 Thread John Goerzen
Itsme (Sophie) wrote:
 It's been quite a response, yes :-)
 
 I was half expecting to be received like a spam-bot.

Ahh, well if your late deceased father had left behind $13 BILLION
($13,000,000,000) USD in Nigeria, or if you were selling che$p blu3
pi11s, then you would have been received that way :-)

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


[Haskell-cafe] Re: Tests

2009-05-05 Thread John Goerzen
Guenther Schmidt wrote:
 let me first of all thank you for providing the HDBC package. Haskell 
 would be a much, much less usefull language without a working database 
 interface. I could certainly not have written the app in  Haskell 
 without it and in any other language I know writing this app would have 
 been much more difficult.

Thanks!  I'm glad you found it (and Real World Haskell) helpful.

 The problem is what's in the database.
 
 You'd think there'd be a Günni in the database, right?
 
 Wrong!
 
 At least this is where your library and Sqlite disagree. Sqlite with any 
 GUI client doesn't show a Günni, it shows a G!$%§$§%nni. So do MS 
 Access and MySql btw.

And now that is REALLY weird, because I can't duplicate it here.

I wrote this little Haskell program:

import Database.HDBC
import Database.HDBC.Sqlite3

main = do dbh - connectSqlite3 foo.db
  run dbh CREATE TABLE foo (bar text) []
  run dbh INSERT INTO foo VALUES (?) [toSql Günther]
  run dbh INSERT INTO foo VALUES (?) [toSql 2-G\252nther]
  commit dbh
  disconnect dbh

And when I inspect foo.db with the sqlite3 command-line tool:

/tmp$ sqlite3 foo.db
SQLite version 3.5.9
Enter .help for instructions
sqlite select * from foo;
Günther
2-Günther

Exactly correct, as expected.

I can read it back correctly from Haskell, too:

import Database.HDBC
import Database.HDBC.Sqlite3
import qualified System.IO.UTF8 as U

main = do dbh - connectSqlite3 foo.db
  results - quickQuery' dbh SELECT * from foo []
  mapM_ ((print :: String - IO ()) . fromSql . head) results
  mapM_ (U.putStrLn . fromSql . head) results
  disconnect dbh

and when I run this:

/tmp$ ./foo3a
G\252nther
2-G\252nther
Günther
2-Günther

I wonder if there is something weird about your environment: non-unicode
terminals, databases, editors, or something?

For me, it Just Works as it should.



 
 For now I managed to rollback the UTF8 code in the HDBC-2.1 and got my 
 app to work as needed.
 
 I hope you find this info useful, thanks once more
 
 Günther
 
 

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


Re: [Haskell-cafe] HDBC 2.1, UTF8 and Umlauts

2009-05-04 Thread John Goerzen
GüŸnther Schmidt wrote:
 Hi guys,
 
 for some reason, any way I try, all the Umlauts get garbled with HDBC 2.1.
 HDBC 1.16 worked fine with any backend (ODBC, Sqlite3, ... what have you).
 
 Anybody else had similar problems and knows how to solve this?

You need to be more specific, but it is likely you are trying to send
something to HDBC that isn't encoded in UTF-8.  HDBC 2.x has a global
preference for UTF-8 now, actually partly to resolve complaints like this.

If you are feeding it ISO-8859-1 data or somesuch, try giving it UTF-8
instead.

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


Re: [Haskell-cafe] HDBC 2.1, UTF8 and Umlauts

2009-05-04 Thread John Goerzen
Guenther Schmidt wrote:
 Hi John,
 
 thanks for taking the time. It actually is \252 that turned into 
 something else because of my email client, damn the thing.

OK, perhaps we have some confusion here.

Are you saying that you entered the Unicode characters directly into
your Haskell source as literals?  In other words, you did not type:

  backslash two five two

but instead just typed the umlaut on the keyboard?

If so, that won't work directly -- I think.  Maybe somebody can correct
me on this, but my hunch is that would save the umlaut as UTF-8 when you
save the .hs file.  Then you will get a String which is supposed to have
 decoded Unicode data, instead having encoded UTF-8 data.

You could wrap it with Codec.Binary.UTF8.String.decodeString from
utf8-string and see if that helps.  If it does, that'll be your problem.

It's a complicated topic, I know.  And the scary thing is that Unicode
makes this all *easier*.



 
 I'll do some further investigating and give you some more details when I 
 have them, thanks in advance.
 
 Günther
 
 
 John Goerzen schrieb:
 On Mon, May 04, 2009 at 04:44:04PM +0200, Guenther Schmidt wrote:
   
 Hi John,

 I'm trying stuff like:

dbc - connectSqlite3 somedatabase
run dbc insert into someTable values (?) [toSql Günni].
 
 SO what do you get back after adding:

  commit
  r - quickQuery' dbc select * from someTable
  print r

 Just knowing it's garbled doesn't help.  Need to know *how* it's
 garbled.

 But the problem is that \374 isn't Unicode at all.  It's ISO-8859-1.
 You're not actually giving it Unicode data to start with.  I believe
 the proper sequence is \252.

 For all I know, \374 may not even be a valid Unicode encoding (haven't
 tested it).

 Try \252.


   
 I also tried:

dbc - connectSqlite3 somedatabase
run dbc insert into someTable values ('Günni') [].

 So since this is Haskell code I presume it's in UTF-8, my emacs stores  
 all my *.hs files as UTF-8

 In either case the ü becomes garbled.

 With the previous version of HDBC, 1.1.6, this worked just fine.


 It also garbles any Umlauts coming *out*, the source is an UTF-8 sqlite3  
 db file.

 Günther



 John Goerzen schrieb:
 
 GüŸnther Schmidt wrote:
   
   
 Hi guys,

 for some reason, any way I try, all the Umlauts get garbled with HDBC 2.1.
 HDBC 1.16 worked fine with any backend (ODBC, Sqlite3, ... what have you).

 Anybody else had similar problems and knows how to solve this?
 
 
 You need to be more specific, but it is likely you are trying to send
 something to HDBC that isn't encoded in UTF-8.  HDBC 2.x has a global
 preference for UTF-8 now, actually partly to resolve complaints like this.

 If you are feeding it ISO-8859-1 data or somesuch, try giving it UTF-8
 instead.

 -- John
   
   
 
 
 
 

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


Re: [Haskell-cafe] HDBC 2.1, UTF8 and Umlauts

2009-05-04 Thread John Goerzen
Günther Schmidt wrote:
 Hi John,
 
 what I just noticed is that *all* strings come back as SqlByteStrings.

That's normal, and pretty much irrelevant, since fromSql takes care of it.

It's documented, even: the SqlByteString is assumed to be in UTF-8, and
is decoded when converted to a String.

It is not correct to have \252 in the SqlByteString.  The proper
sequence there is \xc3\xbc.  When converted to String, *then* it should
be \252.

Are you positive you're seeing \252 in the SqlByteString?  That doesn't
make any sense to me.  It's not a valid UTF-8 encoding.


 
 ie. I get my Günni, (G\252nni), back as an SqlByteString G\252nni  
 instead of an SqlString G\252nni.
 
 So when I cast, ie. fromSql x :: String, I get an G\65533nni, which  
 is where the garbling occurs.
 
 
 BTW this is the 3rd time now that I'm writing the same bloody email,  
 my email client clipped the previous 2.
 
 Günther
 
 

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


Re: [Haskell-cafe] HDBC 2.1, UTF8 and Umlauts

2009-05-04 Thread John Goerzen
Günther Schmidt wrote:
 Hi John,
 
 I'm afraid so.
 
 If it came back as an SqlString G\252nni then it propably wouldn't  
 be a problem.

Can you boil this down to a few-line self-contained test program so I
can try it myself?  I do have test cases for Unicode stuff and they are
all passing here.  I would like to be able to eliminate your environment
as a culprit.

Incidentally, could you run make test in the HDBC-sqlite3 source directory?

 
 
 
 
 Am 04.05.2009 um 20:47 schrieb John Goerzen:
 
 Günther Schmidt wrote:
 Hi John,

 what I just noticed is that *all* strings come back as  
 SqlByteStrings.
 That's normal, and pretty much irrelevant, since fromSql takes care  
 of it.

 It's documented, even: the SqlByteString is assumed to be in UTF-8,  
 and
 is decoded when converted to a String.

 It is not correct to have \252 in the SqlByteString.  The proper
 sequence there is \xc3\xbc.  When converted to String, *then* it  
 should
 be \252.

 Are you positive you're seeing \252 in the SqlByteString?  That  
 doesn't
 make any sense to me.  It's not a valid UTF-8 encoding.

 
 How have Umlauts been behaving on your end? Were they as mean to you  
 as they were to me?
 
 
 
 ie. I get my Günni, (G\252nni), back as an SqlByteString G\252nni
 instead of an SqlString G\252nni.

 So when I cast, ie. fromSql x :: String, I get an G\65533nni, which
 is where the garbling occurs.


 BTW this is the 3rd time now that I'm writing the same bloody email,
 my email client clipped the previous 2.

 Günther


 
 

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


Re: [Haskell-cafe] HDBC 2.1, UTF8 and Umlauts

2009-05-04 Thread John Goerzen
Günther Schmidt wrote:
 Am 04.05.2009 um 21:07 schrieb John Goerzen:
 
 Günther Schmidt wrote:
 Hi John,

 I'm afraid so.

 If it came back as an SqlString G\252nni then it propably wouldn't
 be a problem.
 Can you boil this down to a few-line self-contained test program so I
 can try it myself?  I do have test cases for Unicode stuff and they  
 are
 all passing here.  I would like to be able to eliminate your  
 environment
 as a culprit.

 I'll try, it will take me some time since I've never written a test in  
 haskell.

You don't really have to make a special unit test.  Just a simple client
program that creates a table, inserts some data, reads it back, and
demonstrates the corruption.

 That'll be harder to do since I'm on XP here, but I'll try that too,

No problem.  It's just

runghc setup configure -f buildtests
runghc setup build

and just run runtests






 Am 04.05.2009 um 20:47 schrieb John Goerzen:

 Günther Schmidt wrote:
 Hi John,

 what I just noticed is that *all* strings come back as
 SqlByteStrings.
 That's normal, and pretty much irrelevant, since fromSql takes care
 of it.

 It's documented, even: the SqlByteString is assumed to be in UTF-8,
 and
 is decoded when converted to a String.

 It is not correct to have \252 in the SqlByteString.  The proper
 sequence there is \xc3\xbc.  When converted to String, *then* it
 should
 be \252.

 Are you positive you're seeing \252 in the SqlByteString?  That
 doesn't
 make any sense to me.  It's not a valid UTF-8 encoding.

 How have Umlauts been behaving on your end? Were they as mean to you
 as they were to me?



 ie. I get my Günni, (G\252nni), back as an SqlByteString G 
 \252nni
 instead of an SqlString G\252nni.

 So when I cast, ie. fromSql x :: String, I get an G\65533nni,  
 which
 is where the garbling occurs.


 BTW this is the 3rd time now that I'm writing the same bloody  
 email,
 my email client clipped the previous 2.

 Günther



 
 

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


Re: [Haskell-cafe] subscribing to the comments, online Real World Haskell

2009-04-27 Thread John Goerzen
Michael P Mossey wrote:
 Michael P Mossey wrote:
 However, I would like some ability to subscribe to specific comments. I 
 want to see if people have replied to me or what the latest discussion is.
 
 Okay, to follow up my own post, I discovered the subscription 
 button for each chapter. That's good. However, using Live 
 Bookmarks in Firefox, I have a problem... the links that should 
 bring me to the book itself (with the comment in context) are 
 broken. Maybe this is the fault of Live Bookmarks. Anyone 
 recommend another program for subscribing to comments?

I recommend bloglines.com -- pretty nice interface and works well.

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


Re: [Haskell-cafe] HPong-0.1.2 fails to compile in Debian ghc 6.10.1

2009-04-23 Thread John Goerzen
Ahn, Ki Yung wrote:
 I don't know the exact reason but this should not fail since I have 
 Debian packaged ghc 6.10.1 and OpenGL-2.2.1.1 on my system.
 
 I think this is because the filename of the OpenGL shared library is 
 /usr/lib/libGL.so.1 rather than libGL.so.  This is why we have two 

No.  Do not manually create the symlink.  It sounds like you don't have
the -dev packages for OpenGL installed.  You should install them and
then you should be OK.

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


Re: [Haskell-cafe] [ANN] Hack: a sexy Haskell Webserver Interface ^^

2009-04-20 Thread John Goerzen
Andrew Coppin wrote:
 Joe Fredette wrote:
 We need to start referring to more haskell packages as sexy
 
 Would *you* want to copulate with it? ;-)

Hey, it's a safe and pure language, right? ;-)

 
 Hmm, no documentation... GHC log is complaining that mps is missing. 
 Pitty.
 
 ___
 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] GHC including System.Time but not Data.Time?

2009-04-15 Thread John Goerzen
Lennart Augustsson wrote:
 Removing a package in a minor release is, to quote, an epic fail.
 I don't understand how that could be done.

I agree.  Is there any chance of 6.10.3 reverting the change?

-- John

 
   -- Lennart
 
 On Tue, Apr 14, 2009 at 6:56 PM, Bulat Ziganshin
 bulat.zigans...@gmail.com wrote:
 Hello John,

 Tuesday, April 14, 2009, 8:44:12 PM, you wrote:

 I understand the goal of removing stuff from GHC, but the practical
 implications can be rather annoying.
 i think that Haskell Platform will eventually replace what GHC was for
 a years, i.e. out-of-box solution for practical haskell usage. and ghc
 should be just what its name implies - bare compiler

 but i agree that stripping one package in minor 6.10.2 version, w/o
 Haskell Platform really available was an error

 --
 Best regards,
  Bulatmailto:bulat.zigans...@gmail.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


[Haskell-cafe] GHC including System.Time but not Data.Time?

2009-04-14 Thread John Goerzen
Hi folks,

Apologies in advance because this sounds rantish...

So I went to my friendly API reference at
http://www.haskell.org/ghc/docs/latest/html/libraries/index.html and
noticed that I couldn't find Data.Time there anymore.  Though it was
still at
http://www.haskell.org/ghc/docs/6.10.1/html/libraries/index.html

After some checking on IRC, apparently this is on purpose.

I find it *incredibly* annoying, and leaves us with the following
unfortunate set of circumstances:

1) GHC ships with NO way to do date/time calculations in the preferred
   way (Data.Time)

2) GHC's docs reference only the obsolete (System.Time) way of doing
   things, with no reference to the preferred way.

3) I can't tell people to just install GHC and expect them to be able
   to perform date  time calculations the preferred way.  Just about EVERY 
other
   language (C, Perl, Java, Python, etc.) come with this as part of
   the base install.

4) I can't update all my apps to use Data.Time without worrying about
   Yet Another Dependency.

5) Result: black eye on us.

As I saw on IRC:

quicksilver the system isn't supposed to work out the box.
quicksilver the haskell platform is supposed to work out of the box.
quicksilver (shame it doesn't exist)

Which is a fine goal, but until then, pretty please don't go dropping
Data.Time out of GHC.

I understand the goal of removing stuff from GHC, but the practical
implications can be rather annoying.

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


Re: [Haskell-cafe] System.Process.Posix

2009-04-07 Thread John Goerzen
Bulat Ziganshin wrote:
 Hello Cristiano,
 
 Sunday, April 5, 2009, 12:05:02 AM, you wrote:
 
 Is it me or the above package is not included in Hoogle?
 
 afair, Neil, being windows user, includes only packages available for
 his own system
 
 there was a large thread a few months ago and many peoples voted for
 excluding any OS-specific packages at all since this decreases
 portability of code developed by Hoogle users :)))
 
 

Urm, I realize that was half in jest, but no.  It just makes Hoogle less
useful.  If I need to fork, I need to fork, and no amount of
sugarcoating is going to get around that.

-- John

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


[Haskell-cafe] QC 2.0 missing some stuff I need

2009-03-11 Thread John Goerzen
Hi,

QuickCheck 1.x had this function:

evaluate :: Testable a = a - Gen Result

which I used in TestPack to help wrap a QuickCheck test as a HUnit
test case.  QuickCheck 2.x seems to have no pure evaluate-like
function at all; all of its functions are in the IO monad and also
write their result to stdout, according to the docs.  Am I missing
something?

Thanks,

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


[Haskell-cafe] Re: Migration to QuickCheck 2.0

2009-03-06 Thread John Goerzen
John Goerzen wrote:
 Hi,
 
 My google skills must be faulty, because I can't find much stuff on
 migrating from QuickCheck 1.0 to 2.0.
 
 I've got a number of questions:
 
 What's the deal with Result and reason being in two different places
 in QuickCheck with two different definitions?
 
 All the QC.Config -- configMaxTest, defaultConfig, arguments, etc. are
 missing.  Are there direct replacements?

OK, ignore the second one.  That was an HUnit question; sorry.

 
 Thanks,
 
 -- John

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


Re: [Haskell-cafe] ANNOUNCE: tar 0.3.0.0

2009-03-02 Thread John Goerzen
Duncan Coutts wrote:
 All,
 
 I'm pleased to announce a major new release of the tar package for
 handling .tar archive files.

Very nice!

I'm curious -- what specific variants of the tar format can it read and
write?

 * PAX?
 * GNU tar sparse files?
 * POSIX ustar
 * various pre-posix archives?
 * Solaris tar?
 * Binary and text numbers in numeric fields?

-- John
 

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


Re: [Haskell-cafe] Re: Basic problem in Haskell language design?

2009-03-02 Thread John Goerzen
Stuart Cook wrote:
 On Mon, Mar 2, 2009 at 12:35 AM, Achim Schneider bars...@web.de wrote:
 -Wall? The number of -W options enabled should scale (at least)
 linearly with code size.
 
 To make this a little more clear:
 
 You should probably be using the -Wall compiler option, which will
 produce a message for code constructs that the compiler finds
 suspicious.
 
 In your case you should see three relevant warnings:
 
 1. moverFromWord8s is defined but not used
 2. moverFromWord8s has no explicit type signature
 3. movesFromWord8s has a non-exhaustive pattern match

And that warning #3 is the one that you really should care about.  It'll
save you.

-- John

 
 
 Stuart
 ___
 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] Can this be done?

2009-02-11 Thread John Goerzen
On Wed, Feb 11, 2009 at 09:43:34PM +0800, Evan Laforge wrote:
 On Wed, Feb 11, 2009 at 9:34 PM, Alistair Bayley alist...@abayley.org wrote:
  2009/2/11 Cristiano Paris cristiano.pa...@gmail.com:
  I wonder whether this can be done in Haskell (see muleherd's comment):
 
  http://www.reddit.com/r/programming/comments/7wi7s/how_continuationbased_web_frameworks_work/
 
  WASH did/does something similar. You can certainly write applications
  in a similar, workflow-ish style (rather than like a state machine).
 
 To hijack the subject, what happened to WASH?  The paper seemed like
 it was full of interesting ideas, but the implementation seems to have
 failed to capture many hearts.  Now it seems like a stagnant project.
 What were the fatal flaws?

I actually used it in production for some time, and abandoned it in
favor of a FastCGI-based app about 6 months ago.

There were several issues.  The biggest was maintainability.  CPS was
difficult to work with, especially when different paths through a web
app branch and may later reunite.  There was not enough control over
how things worked, and the HTML and JavaScript generated did not
always fit our needs.  Field names were essentially random, and IIRC,
so were page names, making integration with other web sites
difficult.  You can't just link from an external static HTML to a
particular page or to the submission of a particular form.

There were also issues with people using the back button.

It reminded me a fair bit of the issues I ran into when using Python's
Twisted framework, actually.

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


Re: [Haskell-cafe] Are you using Haskell on the job?

2009-02-06 Thread John Goerzen
Kirk Martinez wrote:
 Hello, fellow Haskell hackers!  I am writing a term paper on Haskell in
 Business, and while I have gathered a lot of good information on the

I do hope you will publish your results somewhere.

 * What were the pros and cons you considered when choosing a
   language?  Why FP?  Why Haskell?

Haskell's static type checking plus type inference were a big win.  Java
is so heavy-handed with its type system (yet not actually achieving real
safety; see NullPointerException and ClassCastException) that is is a
significant hindrance to productivity.  Python is an agile language to
write in, but things can sometimes blow up in your face long after you
thought they were stable.

Type inference is a killer feature in my book.

Killer feature #2 is purity.  It is just a really... freeing experience.
   I worry less about my Haskell code than I did about my Python code.

 * What aspects of your problem domain were most critical to making
   that choice?

The need for stability of code in production.

 * How has using Haskell given you a competitive advantage?

It has been, on more than one occasion, faster to write both an
application and a library in Haskell that it would have been to write
just the application in some other language.

FFI also plays into that, thanks to some dinosaur proprietary software.

But in the long run, our Haskell code is *solid*.  OK, so there are
occasional read-generated exceptions, but knowing to avoid that
particular pitfall is easy and not burdensome.

Bottom line: it is fast to write, and it works well.

 * How is the software development lifecycle positively/negatively
   affected by using Haskell as opposed to a different language?

Compared to Python, my Haskell code is more likely to work when it
manages to compile, and less likely to discover some weird type error
after already going into production.  Shorter development lifecycle
there.  Shorter testing cycle, and less hacking once it's in production.

Back when we had AIX on-site, the benefit was not as clear.  AIX was not
well-supported by GHC, and I had to invest a non-trivial amount of time
maintaining it there.

OTOH, I had to invest a non-trivial amount of time just maintaining gcc
and binutils there as well, so pick your poison I guess.  Python worked
pretty much out of the box on AIX.

 * How did you convince management to go with a functional approach?

I am management.  It never came up :-)

 * Was the relative scarcity of Haskell programmers a problem?  If
   so, how was it managed?

Yes and no.  I don't hire people because they know $LANGUAGE.  I hire
people that are adaptable and love to learn new things.  Finding time
for them to learn Haskell has been an issue, and we haven't done it yet.
 On the other hand, they already maintain their own GHC development
environments, and when I've been at conferences, they've successfully
done a small bit of Haskell hacking for urgent problems.

I am not concerned about them being able to learn Haskell, or about
finding people with that ability.  I'm somewhat concerned about us
finding the time to permit them to do so though.

 * Would you choose to use Haskell again for a similar project given
   what you know now?

Absolutely.  Though I would not use WASH or HSQL again.


 The best responses will not simply list answers, but also provide
 background and a bit of narrative on the project and insights gained.
 Feel free to reply to the list, or just to me personally if you
 prefer.

I have used Haskell for quite a few integration projects: data from
vendor X has to go into a database from an app by vendor Y, and
vice-versa.  There is a lot of parsing, a lot of formatting, and a lot
of database interactions and data validation.  It is messy: sometimes
we get data in a format it shouldn't be in, sometimes we get errors, and
we have to deal with this.  One of my coworkers instinctively reaches
for Perl for this, and I instinctively reach for Haskell.  They both
seem to work pretty well for it -- I think Haskell with Parsec works
better than Perl, actually, thanks to its helpful error messages.

Haskell was also at the heart of a system that we (a lawn mower
manufacturer) pushed out to our dealers, letting them register the
warranty on units they've sold and request rebates on a private website.
 This project requires data validation in several disparate systems and
complex business rules governing eligibility and penalties for late
submission.

This was initially written using WASH, but rewritten to FastCGI plus a
custom utility module.  It also initially used HSQL, but I wrote HDBC
mainly due to bugs and deficiencies in HSQL for this particular project.
 One database involved is a dinosaur proprietary system that supports
ODBC but not unixODBC and is about 7 years out of date.  We maintain a
private branch of HDBC-ODBC to get it to compile with this.  No language
binding worked with it out of the box.

Haskell 

[Haskell-cafe] Re: hslogger bugs or features?

2009-02-03 Thread John Goerzen
Marc Weber wrote:
 Following the advice on the hslogger wiki
 (http://software.complete.org/software/wiki/hslogger)
 I'm posting my thoughts about hslogger here:

Hi Marc,

Thanks for posting this.

Let's start with a big-picture architecture overview.  What need does
hslogger anticipate meeting?

* Big applications have varied logging needs.

* Small applications want to keep logging simple.

* It is often desirable to enable or disable logging about certain types
of things.

* It is also often desirable to enable or disable logging above a
certain threshold of importance.

* The vast majority of apps want to set logging preferences once and
then forget about them, having decided what to do by reading a config
file, command line, or whatever.

* There can be many different ways to output logging messages: syslog,
stderr, files, etc.  A given app may want to use more than one of them.

There are a lot of logging frameworks out there.  Many of them fail the
keep logging simple test.  Many others fail the varied needs test.
One that failed neither in my experience was the Python logging
infrastructure, so I based hslogger around its interface.  hslogger has
served me pretty well since, though I wish it were a bit stronger on the
simple side.


 This piece of code (src/System/Log/Logger.hs):
 
parentHandlers name =
 let pname = (head . drop 1 . reverse . componentsOfName) name
 in do 
 [...]
 next - parentHandlers pname
 return ((handlers parent) ++ next)
 
 Why?
 Because when logging to A.B.C it splits the String once to get
 [A,B,C], then it drops the last part and runs the same again for
 A.B and so on..
 So A string is split  3 times for one logging action. I think this is a
 waste of cpu cycles.. I'm going to improve this. While reading the code
 i noticed two issues:

It may be, but really this is trivially tiny.  The effort required to do
that is almost certainly exceptionally tiny compared just to the effort
required to actually output the log message.  If you have a simple fix,
that's fine, but let's not complicate the code to save a 2 CPU cycles in
a process that can't possibly use less than 1000 :-)

 ==
 issue 1
 
 That's not the most awkward thing:
   When logging to A.B.C hslogger does add 3 loggers to the global
   logger Map:

Only if you haven't logged to it before.

   A
   A.B
   A.B.C
   all three inheriting the default priority level of the default
   rootLogger 

According to the docs:

  First of all, whenever you first access a given logger by name, it
  magically springs to life.  It has a default 'Priority' of 'DEBUG'
  and an empty handler list -- which means that it will inherit whatever
  its parents do.

It's not setting the priority to the rootLogger default; it's setting it
to DEBUG.  Your test doesn't invalidate this.

 A test application illustrating this (feature ?)
 
   module Main where
   -- packages: hslogger
   import  System.Log.Logger as HL
   import  System.Log.Handler.Simple as HL
 
   main = do
 -- the default logger logs to stderr level WARNING 
 -- that's why the following message should be shown 
 
 -- a)
 logM A.B.C HL.ALERT ALERT test, should be shown and should create the 
 sublogger
 
 -- b)
 updateGlobalLogger rootLoggerName (setLevel EMERGENCY)
 
 logM A.B.C HL.ALERT ALERT test, should not be shown cause we have 
 changed to EMERGENCY
 
 which prints:
 
   tmp %./test1
   /tmp nixos   
   ALERT test, should be shown and should create the sublogger
   ALERT test, should not be shown cause we have changed to EMERGENCY
 
 which is quite confusing because I haven't told hslogger explicitely
 to use a log level printing ALERTs on A.B.C. so I'd expect that only

No, you told it that things logged to the root logger directly have a
certain preference.  You have never expressed any preference whatsoever
on the A.B.C logger.

If you wish to set a global preference on the level of logging to occur,
you would be better served to do so in the configuration for the
handler.  From the docs:

  To give you one extra little knob to turn, 'LogHandler's can also have
  importance levels ('Priority') associated with them in the same way
  that 'Logger's do.  They act just like the 'Priority' value in the
  'Logger's -- as a filter.  It's useful, for instance, to make sure
  that under no circumstances will a mere 'DEBUG' message show up in
  your syslog.

Since handlers are inherited down the logger chain, you can easily tweak
the priority associated with the handlers at the root logger level and
have an instant impact on all the others.

The point of the priority attached to a logger is to be able to disable
messages *about* certain things.

The point of the priority attached to a handler is to be able to disable
messages *below a certain importance level globally*.

So I think you're trying to 

Re: [Haskell-cafe] hslogger bugs or features - patches

2009-02-03 Thread John Goerzen
Marc Weber wrote:
 
 I've written some patches increasing speed by 30%. See the benchmark.

Hi Marc,

Patches are always great to see!  Where is this benchmark?

Can you separate out your speed changes (which I take it have no impact
on functionality or API) from your other changes?  I am not certain that
I would want to apply the other changes.

 You can get them by cloning git://mawercer.de/hslogger;
 (branch hslogger_updates)
 
 I've replaced the internal representation (Map name Logger) by a tree.
 Only logging to a logger does no longer add a new node (which cloned the
 priority level in the past causing issue 1)

As I said, I'm not really convinced this is a real issue.  I'm still
open to it though -- but I'm unconvinced that the change in API is worth
it at this point.

 Also I've removed the standard setup logging to stderr. There is a 
 setupLogging function instead..

I'm not sure what you mean the standard setup logging to stderr.  Do
you mean the default root handler?

 Why? I can think of some use cases where logging to stderr doesn't make
 sense and it took me too much time figuring out how to remve the old
 stderr logger (I didn't find a nice solution without changing the
 exposed API)

You didn't notice setHandlers?

  -- | Set the 'Logger'\'s list of handlers to the list supplied.
  -- All existing handlers are removed first.
  setHandlers :: LogHandler a = [a] - Logger - Logger

It is perfectly valid to set the root logger's handlers to [] if you
want it to do nothing at all.

 I don't want to start using my personal copy of hslogger. That's why
 I'd like to ask you wether you consider these changes beeing
 improvements although they break existing code (You'll have do add that
 initialization line)

At this point, I'm not convinced that the API changes are actual
improvements.  But I'm not saying never.

 I also wonder wether it's worth using Bytestrings instead of Strings?

To what end?  The only reason I can think of is UTF-8 output.

(does putStr output UTF-8 these days, or still truncate the 24 bits
above the low 8 like it used to?  I haven't checked.)

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


Re: [Haskell-cafe] Bytestrings vs String? parameters within package names?

2009-02-03 Thread John Goerzen
Marc Weber wrote:
 On Mon, Feb 02, 2009 at 10:41:57PM -0500, wren ng thornton wrote:
  Marc Weber wrote:
 Should there be two versions?
 hslogger-bytestring and hslogger-string?
  I'd just stick with one (with a module for hiding the conversions, as 
  desired). Duplicating the code introduces too much room for maintenance and 
  compatibility issues.

  That's the big thing. The more people that use ByteStrings the less need 
  there is to convert when combining libraries. That said, ByteStrings aren't 
  a panacea; lists and laziness are very useful.
 
 Hi wren,
 
 In the second paragraph you agree that there will be less onversion when
 using only one type of strings.

Incidentally, I already wrote a library that abstracts the difference
between a String and a ByteString: ListLike.

I don't think anybody, including me, even uses it now.  Turns out that's
not all that helpful an abstraction to make ;-)

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


  1   2   3   4   5   >