{-# LANGUAGE CPP #-}
#define dummy   -- just to ensure that cpp gets called on this file
module Text.XML.HaXml.Wrappers
  ( fix2Args
  , processXmlWith
  , onContent
  ) where

-- imports required for processXmlWith and fix2Args
import Prelude hiding (filter)
import System.Exit
import System.Environment
import System.IO
import Data.List  (isSuffixOf)
import Control.Monad (when)

import Text.XML.HaXml.Types       (Document(..),Content(..))
import Text.XML.HaXml.Combinators (CFilter)
import Text.XML.HaXml.Posn        (Posn,posInNewCxt)
import Text.XML.HaXml.Parse       (xmlParse)
import Text.XML.HaXml.Html.Parse  (htmlParse)
import Text.XML.HaXml.Pretty as PP(document)
import Text.XML.HaXml.Version
import Text.PrettyPrint.HughesPJ  (render)


-- | This useful auxiliary checks the commandline arguments for two
--   filenames, the input and output file respectively.  If either
--   is missing, it is replaced by '-', which can be interpreted by the
--   caller as stdin and\/or stdout.
fix2Args :: IO (String,String)
fix2Args :: IO (String, String)
fix2Args = do
  [String]
args <- IO [String]
getArgs
  forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (String
"--version" forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
args) forall a b. (a -> b) -> a -> b
$ do
      String -> IO ()
putStrLn forall a b. (a -> b) -> a -> b
$ String
"part of HaXml-" forall a. [a] -> [a] -> [a]
++ String
version
      forall a. IO a
exitSuccess
  forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when (String
"--help" forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [String]
args) forall a b. (a -> b) -> a -> b
$ do
      String -> IO ()
putStrLn String
"See http://projects.haskell.org/HaXml"
      forall a. IO a
exitSuccess
  case forall (t :: * -> *) a. Foldable t => t a -> Int
length [String]
args of
    Int
0 -> forall (m :: * -> *) a. Monad m => a -> m a
return (String
"-",     String
"-")
    Int
1 -> forall (m :: * -> *) a. Monad m => a -> m a
return ([String]
argsforall a. [a] -> Int -> a
!!Int
0, String
"-")
    Int
2 -> forall (m :: * -> *) a. Monad m => a -> m a
return ([String]
argsforall a. [a] -> Int -> a
!!Int
0, [String]
argsforall a. [a] -> Int -> a
!!Int
1)
    Int
_ -> do String
prog <- IO String
getProgName
            String -> IO ()
putStrLn (String
"Usage: "forall a. [a] -> [a] -> [a]
++String
progforall a. [a] -> [a] -> [a]
++String
" [infile] [outfile]")
            forall a. IO a
exitFailure


-- | The wrapper @processXmlWith@ returns an IO () computation
--   that collects the filenames (or stdin\/stdout) to use when
--   reading\/writing XML documents.  Its CFilter argument
--   is applied to transform the XML document from the input and
--   write it to the output.  No DTD is attached to the output.
--
--   If the input filename ends with .html or .htm, it is parsed using
--   the error-correcting HTML parser rather than the strict XML parser.
processXmlWith :: CFilter Posn -> IO ()
processXmlWith :: CFilter Posn -> IO ()
processXmlWith CFilter Posn
f = do
  (String
inf,String
outf) <- IO (String, String)
fix2Args
  String
input      <- if String
infforall a. Eq a => a -> a -> Bool
==String
"-" then IO String
getContents else String -> IO String
readFile String
inf
  Handle
o          <- if String
outfforall a. Eq a => a -> a -> Bool
==String
"-" then forall (m :: * -> *) a. Monad m => a -> m a
return Handle
stdout else String -> IOMode -> IO Handle
openFile String
outf IOMode
WriteMode
  String -> Document Posn
parse      <- if String
".html" forall a. Eq a => [a] -> [a] -> Bool
`isSuffixOf` String
inf Bool -> Bool -> Bool
|| String
".htm" forall a. Eq a => [a] -> [a] -> Bool
`isSuffixOf` String
inf
                then forall (m :: * -> *) a. Monad m => a -> m a
return (String -> String -> Document Posn
htmlParse String
inf)
                else forall (m :: * -> *) a. Monad m => a -> m a
return (String -> String -> Document Posn
xmlParse String
inf)
  ( Handle -> String -> IO ()
hPutStrLn Handle
o forall b c a. (b -> c) -> (a -> b) -> a -> c
. Doc -> String
render forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall i. Document i -> Doc
PP.document forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> CFilter Posn -> Document Posn -> Document Posn
onContent String
inf CFilter Posn
f forall b c a. (b -> c) -> (a -> b) -> a -> c
. String -> Document Posn
parse ) String
input
  Handle -> IO ()
hFlush Handle
o

  where
    onContent :: FilePath -> CFilter Posn -> Document Posn -> Document Posn
    onContent :: String -> CFilter Posn -> Document Posn -> Document Posn
onContent String
file CFilter Posn
filter (Document Prolog
p SymTab EntityDef
s Element Posn
e [Misc]
m) =
        case CFilter Posn
filter (forall i. Element i -> i -> Content i
CElem Element Posn
e (String -> Maybe Posn -> Posn
posInNewCxt String
file forall a. Maybe a
Nothing)) of
            [CElem Element Posn
e' Posn
_] -> forall i.
Prolog -> SymTab EntityDef -> Element i -> [Misc] -> Document i
Document Prolog
p SymTab EntityDef
s Element Posn
e' [Misc]
m
            []           -> forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"filtering"forall a. [a] -> [a] -> [a]
++String
fileforall a. [a] -> [a] -> [a]
++String
"produced no output"
            [Content Posn]
_            -> forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"filtering"forall a. [a] -> [a] -> [a]
++String
fileforall a. [a] -> [a] -> [a]
++
                                    String
"produced more than one output document"

-- | The wrapper @onContent@ simply applies a given content filter to a
--   document.  Ambiguous or empty results raise an error exception.
onContent :: CFilter i -> Document i -> Document i
onContent :: forall i. CFilter i -> Document i -> Document i
onContent CFilter i
filter (Document Prolog
p SymTab EntityDef
s Element i
e [Misc]
m) =
    case CFilter i
filter (forall i. Element i -> i -> Content i
CElem Element i
e forall a. HasCallStack => a
undefined) of
      [CElem Element i
e' i
_] -> forall i.
Prolog -> SymTab EntityDef -> Element i -> [Misc] -> Document i
Document Prolog
p SymTab EntityDef
s Element i
e' [Misc]
m
      []           -> forall a. HasCallStack => String -> a
error String
"onContent: produced no output"
      [Content i]
_            -> forall a. HasCallStack => String -> a
error String
"onContent: produced more than one output"