Skip to content

Commit

Permalink
Export arrayEnv in MathML; simplify arrayEnv in LaTeX.
Browse files Browse the repository at this point in the history
  • Loading branch information
jgm committed Mar 24, 2011
1 parent 99d9694 commit 4ca2708
Show file tree
Hide file tree
Showing 2 changed files with 20 additions and 29 deletions.
42 changes: 19 additions & 23 deletions Text/HeX/Math/LaTeX.hs
Expand Up @@ -335,15 +335,15 @@ defaults = do
, "Vert"
, "ulcorner"
, "urcorner" ]
mapM_ (arrayEnv True) [ "array"
, "pmatrix"
, "vmatrix"
, "bmatrix"
, "Vmatrix"
, "Bmatrix" ]
mapM_ (arrayEnv False) [ "eqnarray"
, "align"
, "cases" ]
mapM_ arrayEnv [ "array"
, "pmatrix"
, "vmatrix"
, "bmatrix"
, "Vmatrix"
, "Bmatrix"
, "eqnarray"
, "align"
, "cases" ]
addParser [Math] enclosure

enclosure :: HeX Doc
Expand All @@ -360,20 +360,16 @@ latexCommand2 :: String -> HeX ()
latexCommand2 s = newCommand [Math] s $ \(MathDoc d1) (MathDoc d2) ->
ctl s +++ d1 +++ d2

arrayEnv :: Bool -> String -> HeX ()
arrayEnv opt s =
if opt
then newEnvironment [Math] s arrayBody
else newEnvironment [Math] s $ arrayBody Nothing
where
arrayBody (mbopt :: Maybe String) = do
lns <- arrayLines math
return $ "\\begin{" +++ raws s +++ "}" +++
(case mbopt of
Nothing -> mempty
Just x -> "[" +++ raws x +++ "]") +++ "\n" +++
(mintercalate "\\\\\n" $ map (mintercalate " & ") lns) +++
"\\end{" +++ raws s +++ "}"
arrayEnv :: String -> HeX ()
arrayEnv s =
newEnvironment [Math] s $ \(mbopt :: Maybe String) -> do
lns <- arrayLines math
return $ "\\begin{" +++ raws s +++ "}" +++
(case mbopt of
Nothing -> mempty
Just x -> "[" +++ raws x +++ "]") +++ "\n" +++
(mintercalate "\\\\\n" $ map (mintercalate " & ") lns) +++
"\\end{" +++ raws s +++ "}"

mintercalate :: Monoid m => m -> [m] -> m
mintercalate sep items = mconcat $ intersperse sep items
Expand Down
7 changes: 1 addition & 6 deletions Text/HeX/Math/MathML.hs
@@ -1,5 +1,5 @@
{-# LANGUAGE OverloadedStrings, ScopedTypeVariables #-}
module Text.HeX.Math.MathML (defaults) where
module Text.HeX.Math.MathML (defaults, arrayEnv) where

import Text.HeX
import Text.HeX.Standard.Xml
Expand Down Expand Up @@ -571,11 +571,6 @@ arrayEnv s f =
lns <- arrayLines math
return $ f aligns lns

arrayEnv' :: String -> ([[Doc]] -> Doc) -> HeX ()
arrayEnv' s f =
newEnvironment [Math] s $ do
lns <- arrayLines math
return $ f lns


{-
Expand Down

0 comments on commit 4ca2708

Please sign in to comment.