Codebase list mediawiki2latex / upstream/7.36
New upstream version 7.36 Georges Khaznadar 4 years ago
11 changed file(s) with 283 addition(s) and 77 deletion(s). Raw diff Collapse all Expand all
0 Version 7.36
1 * src
2 let a be the fact that mediawiki2latex is asked to gernerate a PDF file
3 or a zip file with the corresponding latex source (which is equivalent
4 to the fact that neigther of the options -b, -d, --epub, --odt
5 are present).
6 let b be the fact that the input is a book or collection (which
7 is equivalent to the fact that -k or --bookmode command line option is present).
8 if both a and b a are true then the memory consumption is reduced by usually at least an
9 order of magnitue. This is why the server now supports up to four requests in parallel
10 and up to four hours per request.
011 Version 7.35
112 * src
213 table column precompilation now happens in a single LaTeX run. This increases speed.
00 Name: mediawiki2latex
1 Version: 7.35
1 Version: 7.36
22 License: GPL
33 License-File: LICENSE
44 Author: Dirk Hünniger <dirk.hunniger@googlemail.com>
5959
6060 getConvert :: FilePath -> String
6161 getConvert p
62 = if os == "linux" then convert else (getPathPrefix p) ++ convert
63 where convert
62 = if os == "linux" then convertexe else (getPathPrefix p) ++ convertexe
63 where convertexe
6464 = if os == "linux" then "convert " else "convert.exe "
6565
6666 {-DHUN| generates the information for the titlepage. It takes the result of the wiki text compilation (CompileResult) as first input parameter and the FullWikiUrl to the article as second parameter. It title information is found in the CompileResult it is used, otherise it is generated from the FullWikiUrl DHUN-}
616616 UserTemplateFile Yes _ -> True
617617 StandardTemplates Yes -> True
618618 ExpandedTemplates Yes -> True
619 _ -> False )then (loadacu st) else
619 _ -> False )then case (loadacu st) of {Right ac->ac;_->[]}else
620620 (parseit (if (runMode cfg) == (HTML No) then minparsers else parsers)
621621 text)))
622622 else return []
0 {-# LANGUAGE DefaultSignatures, DeriveAnyClass, DeriveGeneric #-}
01 {-DHUN| general Fonts configuration modules DHUN-}
12 module BaseFont where
23 import Data.Char
34 import Data.Array
45 import Data.Tuple
5
6 import Data.Serialize
7 import GHC.Generics
68 {-DHUN| Basic Fontstyle, may be either normal of monospaced or small caps DHUN-}
79
810 data FontStyleBase = Normal
911 | Mono
1012 | Smallcaps
11 deriving (Eq, Ord, Show)
13 deriving (Eq, Ord, Show, Read, Serialize, Generic)
1214
1315 {-DHUN| Full discription of style of a font. Consists of Basic Fontstyle plus boolean for bold and/or italic DHUN-}
1416
1517 data FontStyle = FontStyle{stylebase :: FontStyleBase,
1618 bold :: Bool, italic :: Bool}
17 deriving (Eq, Ord, Show)
19 deriving (Eq, Ord, Show, Read, Serialize, Generic)
1820
1921 {-DHUN| Font, a list of ttf font file currently used by mediawiki2latex DHUN-}
2022
3638 | ComputerModernRomanBold
3739 | ComputerModernRomanItalic
3840 | ComputerModernRomanBoldItalic
39 deriving (Eq, Ord, Show, Ix)
41 deriving (Eq, Ord, Show, Ix, Read, Serialize, Generic)
4042
4143 {-DHUN| list of Fonts. The first element in the list is the fonts that is preferred to be used. If it can not be used for some reason the next font in the list is used. Note that the list is denoted in reverse order and put into the right order by the reverse function in the way it is just written at this point of the source file DHUN-}
4244
1616 import Data.ByteString as B
1717 hiding (take, reverse, dropWhile, takeWhile, drop, map, concat,
1818 elem, length, zip, head, filter, minimum, isInfixOf)
19 import Data.Serialize as S (encode)
20
19 import Data.Serialize as S (encode, decode)
20 import Hex
21 import System.Process
22 import System.IO.Temp
23 import System.Directory
2124
2225 runCompile :: String -> FullConfig-> ImperativeMonad ()
2326 runCompile dir cfg
2730 _ -> parsers
2831 cr <- return (printPrepareTree (parseit p t))
2932 liftIO $ B.writeFile (dir </> "output") (encode cr)
33
34
35 runNewTree :: String -> ImperativeMonad ()
36 runNewTree dir
37 = do t <- liftIO $ B.readFile (dir </> "output")
38 let tr=(case S.decode t of {Right k->k::[Anything Char];_->[]})
39 intus <- liftIO $ Tools.readFile (dir </> "intus")
40 let us = read intus
41 let (nus,ntr) = makeLables tr us
42 liftIO $ B.writeFile (dir </> "newtree") (encode ntr)
43 liftIO $ B.writeFile (dir </> "us") (encode nus)
44
45
46 runTreeToLaTeX :: String ->String-> ImperativeMonad ()
47 runTreeToLaTeX instfn dir
48 = do t <- liftIO $ B.readFile (dir </> "newtree")
49 let l=(case S.decode t of {Right k->k;_->[]})
50 inst <- liftIO $ Tools.readFile (instfn </> "inst")
51 let st = read inst
52 let (ltx,newst) = runState (treeToLaTeX2 l) st
53 liftIO $ B.writeFile (dir </> "ltx") (encode (ltx::String))
54 liftIO $ B.writeFile (dir </> "st") (encode newst)
55 liftIO $ Tools.writeFile (dir </> "inst") (show newst)
56
57
3058
3159 {-DHUN| main function to compile mediawiki pages |DHUN-}
3260
72100 templates
73101 tabs
74102 formulas)
75 _ -> do return
76 (run b mylanguage mytitle (loadacu st) (loadacu st)
77 (hostname . fullUrl $ st)
78 templates
79 tabs
80 formulas)
103 _ -> do case loadacu st of
104 Right pt -> return (run b mylanguage mytitle pt pt (hostname . fullUrl $ st) templates tabs formulas)
105 Left pt -> (runcheap b mylanguage mytitle pt (hostname . fullUrl $ st) templates tabs formulas theRunMode)
81106
82107 {-DHUN| pathname of the temporary directory of the compiler |DHUN-}
83108
199224 = zip [1 ..] (map (\ x -> zip [1 ..] (map fun x)) someTables)
200225 theNewSizes = concat (map sizeFun theSizes)
201226 sizeFun (t, k) = map (\ (s, b) -> ([t, s], b)) k
227
228
229
230 runcheap ::
231 Bool ->
232 Maybe String ->
233 String ->
234 [String] ->
235 String ->
236 String -> [[ByteString]] -> Map.Map String Int -> RunMode ->ImperativeMonad CompileResult
237 runcheap _ _ _ input netloc tmpl
238 someTables _ theRunMode
239 = do ntree<-labelit input
240
241
242
243 trst<-ttl3 initialState{urld = analyseNetloc netloc}{tabmap = tm,
244 templateMap =
245 getUserTemplateMap
246 (read tmpl :: [[String]])}{urls =
247 mUrlState
248 ntree} input
249 lis<-mapM treeToLaTeX2ldr input
250 let bdy = doUnicode (concat lis)
251 let tit = getTitle trst
252 let gals = getGalleryNumbers trst
253 let theTables = reverse (tablist trst)
254 let img = (map (\ g -> ((replace '\n' ' ' g))) (getImages trst))
255
256 return CompileResult{images = img, body = bdy, tablelist = theTables,
257 galleryNumbers = gals, title = tit,
258 html = []}
259 where
260 labelit g= foldM labelloc initialUrlState g
261 labelloc us fn = do _ <- liftIO $ Tools.writeFile (fn </> "intus") (show us)
262 _ <- liftIO $
263 system
264 ("mediawiki2latex -x " ++
265 (Hex.hex (show (fullconfigbase{convert = Just (NewTree fn), runMode= theRunMode}))))
266 t <- liftIO $ B.readFile (fn </> "us")
267 case S.decode t of
268 Right nus->return (nus::UrlState)
269 _->return us
270 treeToLaTeX2ext instfn fn = do _ <-liftIO $
271 system
272 ("mediawiki2latex -x " ++
273 (Hex.hex (show (fullconfigbase{convert = Just (TreeToLaTeX instfn fn), runMode= theRunMode}))))
274 return ()
275
276
277 treeToLaTeX2ldr fn = do ltx <- liftIO $ B.readFile (fn </> "ltx")
278 case S.decode ltx of
279 Right lt->return (lt::String)
280 _->return []
281
282
283 -- fullttl::String->[String]->MyState
284 fullttl instfn g = do let hh = instfn:g
285 _<-mapM (\(x,y) ->treeToLaTeX2ext x y) (zip hh (Prelude.tail hh))
286 stx <- liftIO $ B.readFile ((Prelude.last g) </> "st")
287 case S.decode stx of
288 Right nus->return (nus::MyState)
289 _-> undefined
290
291 -- ttl3::MyState->[String]->MyState
292 ttl3 st g = do systempdir <- liftIO getTemporaryDirectory
293 tempdir <- liftIO $
294 createTempDirectory systempdir "MediaWiki2LaTeXStateIO"
295 liftIO (Tools.writeFile (tempdir </> "inst") (show st))
296 sst <- fullttl tempdir g
297 tempdir2 <- liftIO $
298 createTempDirectory systempdir "MediaWiki2LaTeXStateIO"
299 liftIO (Tools.writeFile (tempdir2 </> "inst") (show st{fndict = fndict sst}))
300 fullttl tempdir2 g
301
302 tm = (postproctabmap (maketabmap theNewSizes Map.empty))
303
304
305 fun :: ByteString -> Double
306 fun x
307 = case reads (toString x) of
308 [(f, _)] -> f
309 _ -> (1000.0)
310 theSizes
311 = zip [1 ..] (map (\ x -> zip [1 ..] (map fun x)) someTables)
312 theNewSizes = concat (map sizeFun theSizes)
313 sizeFun (t, k) = map (\ (s, b) -> ([t, s], b)) k
0 {-# LANGUAGE DefaultSignatures, DeriveAnyClass, DeriveGeneric, StandaloneDeriving #-}
01 {-DHUN| module defining the datatypes needed for the outer imperative flow control of the program. All configurtion information needed for single run of the program is stored here. DHUN-}
12 module ImperativeState where
23 import Data.Map.Strict
78 import Control.Concurrent.MVar
89 import Data.List
910 import Network.URL
10
1111 {-DHUN| A type to for errors that might be thrown during the imperative calculation DHUN-}
12
12 import Data.Serialize
13 import GHC.Generics
1314 data MyError = DownloadError String String
1415 | OtherError String
1516 | WikiUrlParseError String
2122 | ToManyOptionsError
2223 | ToManyOutputOptionsError
2324 | PaperError
25
26
27
28 deriving instance Generic Network.URL.URL
29 deriving instance Generic Network.URL.Host
30 deriving instance Generic Network.URL.Protocol
31 deriving instance Generic Network.URL.URLType
32
33 deriving instance Serialize Network.URL.URL
34 deriving instance Serialize Network.URL.Host
35 deriving instance Serialize Network.URL.Protocol
36 deriving instance Serialize Network.URL.URLType
37
2438
2539 {-DHUN| A monad for dealing with errors DHUN-}
2640
8296 = do v <- newMVar (0 :: Int)
8397 return
8498 ImperativeState{audict = [], fullUrl = fullWikiUrlZero,
85 tmpPath = "", counter = v, loadacu = []}
99 tmpPath = "", counter = v, loadacu = Right []}
86100
87101 data ImperativeState = ImperativeState{audict ::
88102 [(Map String Contributor)],
89103 fullUrl :: FullWikiUrl, tmpPath :: String,
90 counter :: MVar Int, loadacu :: [Anything Char]}
104 counter :: MVar Int, loadacu :: Either [FilePath] [Anything Char]}
105
106
91107
92108 data ImageInfo = ImageInfo{wikiFilename :: String,
93109 imageNumber :: Integer, contributorUrls :: [String],
94110 descriptionUrl :: URL}
95 deriving (Show, Read)
111 deriving (Show, Read, Serialize, Generic)
96112
97113 type ImperativeMonad = ExceptT MyError (StateT ImperativeState IO)
98114
99115 data BookMode = Yes | No
100 deriving (Show, Read, Eq)
116 deriving (Show, Read, Eq, Serialize, Generic)
101117
102118 data RunMode = HTML BookMode
103119 | ExpandedTemplates BookMode
104120 | StandardTemplates BookMode
105121 | UserTemplateFile BookMode String
106 deriving (Show, Read, Eq)
122 deriving (Show, Read, Eq, Serialize, Generic)
107123
108124 data SourceMode = Included
109125 | Excluded
110 deriving (Show, Read)
126 deriving (Show, Read, Serialize, Generic)
111127
112128 data OutputType = PlainPDF
113129 | ZipArchive
114130 | EPubFile
115131 | OdtFile
116 deriving (Show, Read, Eq)
132 deriving (Show, Read, Eq, Serialize, Generic)
133
134 data ConvertState = NewTree String | TreeToLaTeX String String | NewLoad String
135 deriving (Show, Read, Eq, Serialize, Generic)
117136
118137 data FullConfig = FullConfig{headers :: Maybe String,
119138 resolution :: Integer, outputFilename :: String,
121140 vector :: Bool, copy :: Maybe String, mainPath :: String,
122141 server :: Maybe Int, outputType :: OutputType,
123142 selfTest :: Maybe (Integer, Integer), compile :: Maybe String,
124 imgctrb :: Maybe String}
125 deriving (Show, Read)
143 imgctrb :: Maybe String, convert:: Maybe (ConvertState)}
144 deriving (Show, Read, Serialize, Generic)
126145
127146 fullconfigbase :: FullConfig
128147 fullconfigbase
130149 outputFilename = "", inputUrl = "", runMode = HTML No, paper = "A4",
131150 vector = False, copy = Nothing, mainPath = "", server = Nothing,
132151 outputType = PlainPDF, selfTest = Nothing, compile = Nothing,
133 imgctrb = Nothing}
152 imgctrb = Nothing, convert =Nothing}
00
11 {-DHUN| This modules converts the parse tree to a latex document DHUN-}
22 module LatexRenderer
3 (treeToLaTeX3, shallowFlatten, prepateTemplate, replace, doUnicode,
3 (treeToLaTeX2, treeToLaTeX3, shallowFlatten, prepateTemplate, replace, doUnicode,
44 getGalleryNumbers, getTitle, initialState, getJ, urld,
55 analyseNetloc, templateMap, getUserTemplateMap, urls, mUrlState,
66 initialUrlState, makeLables, templateRegistry, baseUrl,
2424 import Network.URL
2525 import Control.Monad.Except
2626 import System.Process
27 import Data.Serialize as S (decode)
2827 import HtmlParser (parseHtml)
28 import Data.Serialize as S (encode, decode)
29
2930
3031
3132 notendyet ::
139140 _ -> return ""
140141 where d = (trim (takeWhile (/= '|') text))
141142
142 qBookIncludeAction :: FullConfig-> WikiUrl -> String -> ImperativeMonad String
143 qBookIncludeAction cfg wurl text
144 = if isInfixOf "Vorlage" text then return ("{{" ++ text ++ "}}") else if isInfixOf "Category:" text then return ""
145 else
146 do pp <- (liftIO (print d)) >> myfun
147 case pp of
148 Just p -> do _ <- addContributors d Nothing
149 x <- noinclude wurl ("\n\ndhunparserurl " ++ d ++ "\n\n" ++ p)
150 st <- get
151 systempdir <- liftIO getTemporaryDirectory
152 tempdir <- liftIO $
153 createTempDirectory systempdir "MediaWiki2LaTeXParser"
154 liftIO $ Tools.writeFile (tempdir </> "input") x
155 _ <- liftIO $
156 system
157 ("mediawiki2latex -x " ++
158 (Hex.hex (show (fullconfigbase{compile = Just tempdir, runMode= runMode cfg}))))
159 t <- liftIO $ B.readFile (tempdir </> "output")
160 put st{loadacu = ((case S.decode t of {Right k->k;_->[]})++ (loadacu st) :: [Anything Char])}
161 return x
162 _ -> return ""
143
144 runqBookIncludeAction :: String -> ImperativeMonad ()
145 runqBookIncludeAction dir
146 = do t <- liftIO $ B.readFile (dir </> "bookinput")
147 let (cfg,wurl,text,acu)=(case S.decode t of {Right k->k::(FullConfig,WikiUrl,String,Either [FilePath] [Anything Char]);_->undefined})
148 oldst<-get
149 put oldst{loadacu=acu}
150 _ <- qBookIncludeActionbase cfg wurl text
151 st<-get
152 liftIO $ B.writeFile (dir </> "bookoutput") (S.encode (loadacu st))
153
154
155 qBookIncludeActionbase :: FullConfig-> WikiUrl -> String -> ImperativeMonad String
156 qBookIncludeActionbase cfg wurl text
157 = if isInfixOf "Vorlage" text then return ("{{" ++ text ++ "}}") else if isInfixOf "Category:" text then return ""
158 else
159 do pp <- (liftIO (print d)) >> myfun
160 case pp of
161 Just p -> do _ <- addContributors d Nothing
162 x <- noinclude wurl ("\n\ndhunparserurl " ++ d ++ "\n\n" ++ p)
163 st <- get
164 systempdir <- liftIO getTemporaryDirectory
165 tempdir <- liftIO $
166 createTempDirectory systempdir "MediaWiki2LaTeXParser"
167 liftIO $ Tools.writeFile (tempdir </> "input") x
168 _ <- liftIO $
169 system
170 ("mediawiki2latex -x " ++
171 (Hex.hex (show (fullconfigbase{compile = Just tempdir, runMode= runMode cfg}))))
172 case (loadacu st) of
173 Right base -> do t <- liftIO $ B.readFile (tempdir </> "output")
174 put st{loadacu = Right ((case S.decode t of {Right k->k;_->[]})++ base :: [Anything Char])}
175 Left base -> put st{loadacu = Left (tempdir: base)}
176 return x
177 _ -> return ""
163178 where d = (trim (takeWhile (/= '|') text))
164179 myfun = case (runMode cfg) of
165180 HTML _ -> liftIO (getBookpage d (wurl))
166181 (ExpandedTemplates _) -> (loadMediaWiki d wurl) >>= (return . Just)
167182 _ -> (loadPlain d wurl Nothing) >>= (return . Just)
168183
184 qBookIncludeAction :: FullConfig-> WikiUrl -> String -> ImperativeMonad String
185 qBookIncludeAction cfg wurl text
186 = do sst <- get
187 case (loadacu sst) of
188 Right _ -> if isInfixOf "Vorlage" text then return ("{{" ++ text ++ "}}") else if isInfixOf "Category:" text then return "" else
189 do pp <- (liftIO (print d)) >> myfun
190 case pp of
191 Just p -> do _ <- addContributors d Nothing
192 x <- noinclude wurl ("\n\ndhunparserurl " ++ d ++ "\n\n" ++ p)
193 st <- get
194 systempdir <- liftIO getTemporaryDirectory
195 tempdir <- liftIO $ createTempDirectory systempdir "MediaWiki2LaTeXParser"
196 --liftIO ( Tools.writeFile (t2empdir </> "input") x)
197 _ <- liftIO $ system ("mediawiki2latex -x " ++ (Hex.hex (show (fullconfigbase{compile = Just tempdir, runMode= runMode cfg}))))
198 case (loadacu st) of
199 Right base -> do t <- liftIO $ B.readFile (tempdir </> "output")
200 put st{loadacu = Right ((case S.decode t of {Right k->k;_->[]})++ base :: [Anything Char])}
201 Left base -> put st{loadacu = Left (tempdir: base)}
202 return x
203 _ -> return ""
204 Left _ -> do systempdir <- liftIO getTemporaryDirectory
205 tempdir <- liftIO $ createTempDirectory systempdir "MediaWiki2LaTeXBook"
206 liftIO $ B.writeFile (tempdir </> "bookinput") (S.encode (cfg,wurl,text,loadacu sst))
207 _ <- liftIO $ system ("mediawiki2latex -x " ++ (Hex.hex (show (fullconfigbase{convert = Just (NewLoad tempdir)}))))
208 t <- liftIO $ B.readFile (tempdir </> "bookoutput")
209 oldst<-get
210 let (acu)=(case S.decode t of {Right k->k::Either [FilePath] [Anything Char];_->Right []})
211 put oldst{loadacu=acu}
212 return []
213
214
215 where d = (trim (takeWhile (/= '|') text))
216 myfun = case (runMode cfg) of
217 HTML _ -> liftIO (getBookpage d (wurl))
218 (ExpandedTemplates _) -> (loadMediaWiki d wurl) >>= (return . Just)
219 _ -> (loadPlain d wurl Nothing) >>= (return . Just)
169220
170221 makeUrl :: String -> String -> String -> [Char]
171222 makeUrl lang theFam thePage
473524 load cfg
474525 = do st <- get
475526 case (runMode cfg) of
476 HTML Yes-> loadBook st Nothing cfg
527 HTML Yes-> do if (outputType cfg) `Data.List.elem` [ZipArchive,PlainPDF] then put (st{loadacu=Left []}) else return ()
528 loadBook st Nothing cfg
477529
478530 UserTemplateFile Yes _ -> loadBook st Nothing cfg
479531 StandardTemplates Yes -> loadBook st Nothing cfg
0 {-# LANGUAGE DefaultSignatures, DeriveAnyClass, DeriveGeneric #-}
01 {-DHUN| A module for mutable states used in the programm DHUN-}
12 module MyState where
23 import qualified Data.Map as Map
45 import Control.Monad.Trans.State (State)
56 import MediaWikiParseTree
67 import BaseFont
7
8 import Data.Serialize
9 import GHC.Generics
810 {-DHUN| a type used as mutable state while processing a table. See documentation of the TableHelper module DHUN-}
911
1012 data TableState = TableState{rowCounter :: Int,
2325
2426 data UrlState = UrlState{iUrlState :: Int, sUrlState :: String,
2527 mUrlState :: Map String String}
26 deriving (Show, Eq, Read)
28 deriving (Show, Eq, Read, Serialize, Generic)
2729
2830 {-DHUN| see initial value of the type UrlState DHUN-}
2931
4345 tablist :: [[String]], tabmap :: Map Int (Map Int Double),
4446 fontStack :: [FontStyle], font :: Font, langu :: Maybe String,
4547 forms :: Map String Int, lastChar :: Char, lastFontChanged :: Bool}
46 deriving (Show, Eq)
48 deriving (Show, Eq, Read, Serialize, Generic)
4749
4850 {-DHUN| Renderer is the State monad using MyState as mutable state DHUN-}
4951
6870 {-DHUN| represents an URL to a wiki (not to a page thereof), which is not a sister project of wikipedia, so not wikibooks wikisource, etc. DHUN-}
6971
7072 data WikiBaseUrl = WikiBaseUrl{baseUrl :: String}
71 deriving (Show, Eq)
73 deriving (Show, Eq, Read, Serialize, Generic)
7274
7375 {-DHUN| represents an URL to a wiki (not to a page thereof), which is a sister project of wikipedia, so wikibooks wikisource, etc. DHUN-}
7476
7577 data WikiUrlInfo = WikiUrlInfo{language :: String,
7678 wikitype :: String}
77 deriving (Show, Eq)
79 deriving (Show, Eq, Read, Serialize, Generic)
7880
7981 {-DHUN| represents an URL to a wiki (not to a page thereof), which is either a sister project of wikipedia, so wikibooks wikisource, etc. or isn't a sister project of wikipedia DHUN-}
8082
8183 data WikiUrlData = BaseUrl WikiBaseUrl
8284 | UrlInfo WikiUrlInfo
83 deriving (Show, Eq)
85 deriving (Show, Eq, Read, Serialize, Generic)
8486
8587 {-DHUN| represents an URL to a page on a wiki DHUN-}
8688
8789 data WikiLinkInfo = WikiLinkInfo{urldata :: WikiUrlData,
8890 page :: String}
89 deriving (Show, Eq)
91 deriving (Show, Eq, Read, Serialize, Generic)
131131 filename :: Maybe String, startTime :: Double, barValue :: Double,
132132 lastStepTime :: Double, lastRuntime :: Double, extension :: String,
133133 failed :: Bool}
134
134 deriving (Show)
135135 instance NFData ProgressInfo where
136136 rnf a = a `seq` ()
137137
288288 infoBox "Conversion Failed" $
289289 (mytext "We are sorry the converion failed, please contact our us")
290290
291 currentlyrunning :: Map Int ProgressInfo -> Bool
291 currentlyrunning :: Map Int ProgressInfo -> Int
292292 currentlyrunning m
293 = not
294 (Data.List.all (\ x -> (isJust (filename x)) || (failed x))
293 = sum
294 (Data.List.map (fromEnum.((\ x -> (isNothing (filename x)) && (not (failed x)))))
295295 (Data.Map.Strict.elems m))
296296
297297 wwidth2 :: [Char]
378378 do mytext "The LaTeX source code will be compiled several times to make sure all references are resolved. The whole process will usually take about one minute."
379379 H.br
380380 H.br
381 H.div H.! A.style "font-size:large" $ H.b "There is a time limit of one hour (≈ 200 pages in PDF) on this server!"
381 H.div H.! A.style "font-size:large" $ H.b "There is a time limit of four hours (≈ 2000 pages in PDF) on this server!"
382382 H.br
383383 mytext "Requests taking longer will be terminated and a \"Conversion Failed due to timeout or non zero exit code\" message will be displayed. There is no limit in the downloadable version of the software, see link on right."
384384
430430 if (toString (toStrict output)) == "odt" then
431431 ImperativeState.OdtFile else
432432 ImperativeState.PlainPDF,
433 compile = Nothing, imgctrb = Nothing}
433 compile = Nothing, imgctrb = Nothing, convert=Nothing}
434434 yy <- newEmptyMVar
435435 mm <- takeMVar m
436 _ <- if (not (currentlyrunning mm)) then
436 _ <- if ((currentlyrunning mm)<=3) then
437437 do _ <- forkIO $
438438 do (i, o, e, h) <- runInteractiveCommand
439439 ("mediawiki2latex -x " ++ act)
447447 then "odt" else "pdf")
448448 zz <- forkProgressDriver o m name ss
449449 putMVar yy zz
450 ex h i e ((realToFrac tt) + 3600.0) m zz ss
450 ex h i e ((realToFrac tt) + (4*3600.0)) m zz ss
451451 return ()
452452 else
453453 do putMVar yy (-1)
1212 import Server
1313 import System.FilePath.Posix
1414 import System.Info
15 import Compiler (runCompile)
15 import Compiler (runCompile, runTreeToLaTeX, runNewTree)
1616 import Tools (replace2)
17
17 import Load
1818 {-DHUN| Data structure to repesent a single option on the command line. DHUN-}
1919
2020 data Flag = Verbose
193193
194194 versionHeader :: String
195195 versionHeader
196 = "mediawiki2latex version 7.35\n" ++ (usageInfo header options)
196 = "mediawiki2latex version 7.36\n" ++ (usageInfo header options)
197197
198198 {-DHUN| print the version string of mediawiki2latex. Takes the output of the compilerOpts function as input. Prints the version string if no options were given or the version command was given does noting otherwise DHUN-}
199199
320320 ImperativeState.copy = Nothing, mainPath = "",
321321 server = Nothing, selfTest = Just (s, e),
322322 outputType = PlainPDF, compile = Nothing,
323 imgctrb = Nothing}
323 imgctrb = Nothing, convert=Nothing}
324324 _ -> Left (NotIntegerPairError featuredOption)
325325 _ -> case serverVal of
326326 Just x -> case reads x of
334334 mainPath = "", server = Just z,
335335 outputType = PlainPDF,
336336 selfTest = Nothing, compile = Nothing,
337 imgctrb = Nothing}
337 imgctrb = Nothing, convert=Nothing}
338338 _ -> Left (NotIntegerError serverOption)
339339 _ -> do hexVal <- atMostOne hexPredicate hexen o
340340 case hexVal of
406406 if zipVal then ZipArchive else
407407 if epubVal then EPubFile else
408408 if odtVal then OdtFile else PlainPDF,
409 compile = Nothing, imgctrb = Nothing})
409 compile = Nothing, imgctrb = Nothing, convert=Nothing})
410410
411411 {-DHUN| main entry point of mediawiki2latex DHUN-}
412412
418418 stz <- imperativeStateZero
419419 cwd <- getCurrentDirectory
420420 case (checkOpts cwd (fst o)) of
421 Right x -> case (compile x) of
422 Just dir -> do _ <- (runStateT (runExceptT (runCompile dir x)) stz)
423 return ()
424 _ -> case (imgctrb x) of
421 Right x -> case (convert x) of
422 Just stx -> case stx of
423 NewTree fn -> do _ <- (runStateT (runExceptT (runNewTree fn)) stz)
424 return ()
425 TreeToLaTeX instfn fn -> do _ <- (runStateT (runExceptT (runTreeToLaTeX instfn fn)) stz)
426 return ()
427 NewLoad fn -> do _ <- (runStateT (runExceptT (runqBookIncludeAction fn)) stz)
428 return ()
429 _-> case (compile x) of
430 Just dir -> do _ <- (runStateT (runExceptT (runCompile dir x)) stz)
431 return ()
432 _ -> case (imgctrb x) of
425433 Just dir -> do _ <- (runStateT (runExceptT (runCtrb dir)) stz)
426434 return ()
427435 _ -> case (server x) of