[resend] Web software with Hugs/Windows. Progress!

I now have HXml Toolbox running under Hugs/Windows, as in:
[[
HUnitExample.hs
Main> main
:
Cases: 110 Tried: 110 Errors: 0 Failures: 0
Counts{cases=110,tried=110,errors=0,failures=0}
]]
The code still needs some tidying up, and I'm not yet sure if this test
case exercises the new POpen module for Windows that I have written. But I
felt it might be appropriate to open discussion about putting my changes
and fixes into "community space".
To get HXml Toolbox running, I have made two areas of changes to common
library code, and further changes to the HXml Toolbox code.
Mush of what follows is predicated on the idea that the Haskell community
would like to absorb my changes back into the common library corpus.
(1) Network.URI
I've written a new parser, and extended the module interface slightly, thus:
[[
module {-Network.-} URI
( -- * The @URI@ type
URI(..)
-- * Parsing a @URI@
, parseURI -- :: String -> Maybe URI
-- * Testing URI categories
, isURI, isURIReference, isRelativeURI, isAbsoluteURI
, isIPv6address, isIPv4address
, testURIReference
-- * Computing relative @URI@s
, relativeTo -- :: URI -> URI -> Maybe URI
-- * Operations on @URI@ strings
-- | support for putting strings into URI-friendly
-- escaped format and getting them back again.
-- This can't be done transparently, because certain characters
-- have different meanings in different kinds of URI.
, reserved, unreserved
, isAllowedInURI, unescapedInURI -- :: Char -> Bool
, escapeChar -- :: (Char->Bool) -> Char -> String
, escapeString -- :: String -> (Char->Bool) -> String
, unEscapeString -- :: String -> String
)
]]
New interfaces are:
, isURI, isURIReference, isRelativeURI, isAbsoluteURI
, isIPv6address, isIPv4address
, testURIReference
(mainly for testing)
unescapedInURI (like isAllowedInURI, but does not include '%')
And an existing internal function that has been exported:
, escapeChar -- :: (Char->Bool) -> Char -> String
I have some concerns about the way URI strings are reassembled from the
component parts using the current URI module interface (e.g. problem with
empty fragment handling noted in a previous message). I think the URI
implementation should be changed so that all the punctuation characters
("//", "?", "#", etc.) are stored as part of the component values in a URI
structure, but I don't know what impact that might have on existing code.
(2) POpen
I have written a (currently partial) POpen replacement for Win32 systems,
based on bits of code I found lying around. As yet, I'm not sure if this
code is actually exercised by the HXml Toolbox. Does anyone have a
stand-alone test module for this?
(3) HTTP module and MD5
I had to scratch around to find a version of the HTTP module with matching
MD5 functions. I eventually found one at:
http://www.dtek.chalmers.se/~d00bring/haskell-xml-rpc/
I think it might be helpful to bring a consistent version into some
"community space", assuming the relevant authors are agreeable.
(4) HXml Toolbox
I expect that, if they're felt to be useful, my changes will be
incorporated by Uwe Schmidt
participants (1)
-
Graham Klyne