module Text.XML.HXT.IO.GetFILE
( getStdinCont
, getCont
)
where
import Control.Exception ( try )
import qualified Data.ByteString.Lazy as B
import Network.URI ( unEscapeString
)
import System.IO.Error ( ioeGetErrorString
)
import System.Directory ( doesFileExist
)
import Text.XML.HXT.DOM.XmlKeywords
getStdinCont :: Bool -> IO (Either ([(String, String)], String) B.ByteString)
getStdinCont strictInput
= do
c <- try ( do
cb <- B.getContents
if strictInput
then B.length cb `seq` return cb
else return cb
)
return (either readErr Right c)
where
readErr e
= Left ( [ (transferStatus, "999")
, (transferMessage, msg)
]
, msg
)
where
msg = "stdin read error: " ++ es
es = ioeGetErrorString e
getCont :: Bool -> String -> IO (Either ([(String, String)], String) B.ByteString)
getCont strictInput source
= do
source'' <- checkFile source'
case source'' of
Nothing -> return $ fileErr "file not found"
Just fn -> do
if False
then return $ fileErr "file not readable"
else do
c <- try $
do
cb <- B.readFile fn
if strictInput
then B.length `seq` return cb
else return cb
return (either readErr Right c)
where
source' = drivePath $ source
readErr e
= fileErr (ioeGetErrorString e)
fileErr msg0
= Left ( [ (transferStatus, "999")
, (transferMessage, msg)
]
, msg
)
where
msg = "file read error: " ++ show msg0 ++ " when accessing " ++ show source'
drivePath ('/' : file@(d : ':' : _more))
| d `elem` ['A'..'Z'] || d `elem` ['a'..'z']
= file
drivePath file
= file
checkFile :: String -> IO (Maybe String)
checkFile fn
= do
exists <- doesFileExist fn
if exists
then return (Just fn)
else do
exists' <- doesFileExist fn'
return ( if exists'
then Just fn'
else Nothing
)
where
fn' = unEscapeString fn