{-# LANGUAGE OverloadedStrings #-}
{-# LANGUAGE ViewPatterns #-}
{-
Copyright (C) 2012 John MacFarlane <jgm@berkeley.edu>

This program is free software; you can redistribute it and/or modify
it under the terms of the GNU General Public License as published by
the Free Software Foundation; either version 2 of the License, or
(at your option) any later version.

This program is distributed in the hope that it will be useful,
but WITHOUT ANY WARRANTY; without even the implied warranty of
MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
GNU General Public License for more details.

You should have received a copy of the GNU General Public License
along with this program; if not, write to the Free Software
Foundation, Inc., 59 Temple Place, Suite 330, Boston, MA  02111-1307  USA
-}

{- | Functions for writing a parsed formula as OMML.
-}

module Text.TeXMath.Writers.OMML (writeOMML)
where

import Text.XML.Light
import Text.TeXMath.Types
import Data.Generics (everywhere, mkT)
import Data.Char (isSymbol, isPunctuation)
import Data.Either (lefts, isLeft, rights)
import qualified Data.Text as T
import Data.List.Split  (splitWhen)

-- | Transforms an expression tree to an OMML XML Tree
writeOMML :: DisplayType -> [Exp] -> Element
writeOMML :: DisplayType -> [Exp] -> Element
writeOMML DisplayType
dt = [Element] -> Element
container forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ([Element] -> Exp -> [Element]
showExp [])
            forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. Data a => a -> a) -> forall a. Data a => a -> a
everywhere (forall a b. (Typeable a, Typeable b) => (b -> b) -> a -> a
mkT forall a b. (a -> b) -> a -> b
$ DisplayType -> [Exp] -> [Exp]
handleDownup DisplayType
dt)
            forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. Data a => a -> a) -> forall a. Data a => a -> a
everywhere (forall a b. (Typeable a, Typeable b) => (b -> b) -> a -> a
mkT forall a b. (a -> b) -> a -> b
$ DisplayType -> [InEDelimited] -> [InEDelimited]
handleDownup' DisplayType
dt)
            forall b c a. (b -> c) -> (a -> b) -> a -> c
. (forall a. Data a => a -> a) -> forall a. Data a => a -> a
everywhere (forall a b. (Typeable a, Typeable b) => (b -> b) -> a -> a
mkT forall a b. (a -> b) -> a -> b
$ [Exp] -> [Exp]
handleScaledDelims)
    where container :: [Element] -> Element
container = case DisplayType
dt of
                  DisplayType
DisplayBlock  -> \[Element]
x -> forall t. Node t => String -> t -> Element
mnode String
"oMathPara"
                                    [ forall t. Node t => String -> t -> Element
mnode String
"oMathParaPr"
                                      forall a b. (a -> b) -> a -> b
$ forall t. Node t => String -> String -> t -> Element
mnodeA String
"jc" String
"center" ()
                                    , forall t. Node t => String -> t -> Element
mnode String
"oMath" [Element]
x ]
                  DisplayType
DisplayInline -> forall t. Node t => String -> t -> Element
mnode String
"oMath"

-- Kept as String for Text.XML.Light
mnode :: Node t => String -> t -> Element
mnode :: forall t. Node t => String -> t -> Element
mnode String
s = forall t. Node t => QName -> t -> Element
node (String -> Maybe String -> Maybe String -> QName
QName String
s forall a. Maybe a
Nothing (forall a. a -> Maybe a
Just String
"m"))

-- Kept as String for Text.XML.Light
mnodeA :: Node t => String -> String -> t -> Element
mnodeA :: forall t. Node t => String -> String -> t -> Element
mnodeA String
s String
v = Attr -> Element -> Element
add_attr (QName -> String -> Attr
Attr (String -> Maybe String -> Maybe String -> QName
QName String
"val" forall a. Maybe a
Nothing (forall a. a -> Maybe a
Just String
"m")) String
v) forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall t. Node t => String -> t -> Element
mnode String
s

str :: [Element] -> T.Text -> Element
str :: [Element] -> Text -> Element
str []    Text
s = forall t. Node t => String -> t -> Element
mnode String
"r" [ forall t. Node t => String -> t -> Element
mnode String
"t" forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
s ]
str [Element]
props Text
s = forall t. Node t => String -> t -> Element
mnode String
"r" [ forall t. Node t => String -> t -> Element
mnode String
"rPr" [Element]
props
                        , forall t. Node t => String -> t -> Element
mnode String
"t" forall a b. (a -> b) -> a -> b
$ Text -> String
T.unpack Text
s ]

showFraction :: [Element] -> FractionType -> Exp -> Exp -> Element
showFraction :: [Element] -> FractionType -> Exp -> Exp -> Element
showFraction [Element]
props FractionType
ft Exp
x Exp
y =
  case FractionType
ft of
       FractionType
NormalFrac -> forall t. Node t => String -> t -> Element
mnode String
"f" [ forall t. Node t => String -> t -> Element
mnode String
"fPr" forall a b. (a -> b) -> a -> b
$
                                forall t. Node t => String -> String -> t -> Element
mnodeA String
"type" String
"bar" ()
                             , forall t. Node t => String -> t -> Element
mnode String
"num" [Element]
x'
                             , forall t. Node t => String -> t -> Element
mnode String
"den" [Element]
y']
       FractionType
DisplayFrac -> [Element] -> FractionType -> Exp -> Exp -> Element
showFraction [Element]
props FractionType
NormalFrac Exp
x Exp
y
       FractionType
InlineFrac -> forall t. Node t => String -> t -> Element
mnode String
"f" [ forall t. Node t => String -> t -> Element
mnode String
"fPr" forall a b. (a -> b) -> a -> b
$
                                 forall t. Node t => String -> String -> t -> Element
mnodeA String
"type" String
"lin" ()
                              , forall t. Node t => String -> t -> Element
mnode String
"num" [Element]
x'
                              , forall t. Node t => String -> t -> Element
mnode String
"den" [Element]
y']
       FractionType
NoLineFrac -> forall t. Node t => String -> t -> Element
mnode String
"f" [ forall t. Node t => String -> t -> Element
mnode String
"fPr" forall a b. (a -> b) -> a -> b
$
                                              forall t. Node t => String -> String -> t -> Element
mnodeA String
"type" String
"noBar" ()
                                             , forall t. Node t => String -> t -> Element
mnode String
"num" [Element]
x'
                                             , forall t. Node t => String -> t -> Element
mnode String
"den" [Element]
y'
                                             ]
    where x' :: [Element]
x' = [Element] -> Exp -> [Element]
showExp [Element]
props Exp
x
          y' :: [Element]
y' = [Element] -> Exp -> [Element]
showExp [Element]
props Exp
y

maximum' :: [Int] -> Int
maximum' :: [Int] -> Int
maximum' [] = Int
0
maximum' [Int]
xs = forall (t :: * -> *) a. (Foldable t, Ord a) => t a -> a
maximum [Int]
xs

makeArray :: [Element] -> [Alignment] -> [ArrayLine] -> Element
makeArray :: [Element] -> [Alignment] -> [ArrayLine] -> Element
makeArray [Element]
props [Alignment]
as [ArrayLine]
rs = forall t. Node t => String -> t -> Element
mnode String
"m" forall a b. (a -> b) -> a -> b
$ Element
mProps forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map forall {t :: * -> *}. Foldable t => [t Exp] -> Element
toMr [ArrayLine]
rs
  where mProps :: Element
mProps = forall t. Node t => String -> t -> Element
mnode String
"mPr"
                  [ forall t. Node t => String -> String -> t -> Element
mnodeA String
"baseJc" String
"center" ()
                  , forall t. Node t => String -> String -> t -> Element
mnodeA String
"plcHide" String
"1" ()
                  , forall t. Node t => String -> t -> Element
mnode String
"mcs" forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map Alignment -> Element
toMc [Alignment]
as' ]
        as' :: [Alignment]
as'    = forall a. Int -> [a] -> [a]
take ([Int] -> Int
maximum' forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map forall (t :: * -> *) a. Foldable t => t a -> Int
length [ArrayLine]
rs) forall a b. (a -> b) -> a -> b
$ [Alignment]
as forall a. [a] -> [a] -> [a]
++ forall a. [a] -> [a]
cycle [Alignment
AlignCenter]
        toMr :: [t Exp] -> Element
toMr [t Exp]
r = forall t. Node t => String -> t -> Element
mnode String
"mr" forall a b. (a -> b) -> a -> b
$ forall a b. (a -> b) -> [a] -> [b]
map (forall t. Node t => String -> t -> Element
mnode String
"e" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ([Element] -> Exp -> [Element]
showExp [Element]
props)) [t Exp]
r
        toMc :: Alignment -> Element
toMc Alignment
a = forall t. Node t => String -> t -> Element
mnode String
"mc" forall a b. (a -> b) -> a -> b
$ forall t. Node t => String -> t -> Element
mnode String
"mcPr"
                            [ forall t. Node t => String -> String -> t -> Element
mnodeA String
"mcJc" (forall {a}. IsString a => Alignment -> a
toAlign Alignment
a) ()
                            , forall t. Node t => String -> String -> t -> Element
mnodeA String
"count" String
"1" ()
                            ]
        toAlign :: Alignment -> a
toAlign Alignment
AlignLeft    = a
"left"
        toAlign Alignment
AlignRight   = a
"right"
        toAlign Alignment
AlignCenter  = a
"center"

makeText :: TextType -> T.Text -> Element
makeText :: TextType -> Text -> Element
makeText TextType
a Text
s = [Element] -> Text -> Element
str (forall t. Node t => String -> t -> Element
mnode String
"nor" () forall a. a -> [a] -> [a]
: TextType -> [Element]
setProps TextType
a) Text
s

defaultTo :: TextType -> [Element] -> [Element]
defaultTo :: TextType -> [Element] -> [Element]
defaultTo TextType
tt [] = TextType -> [Element]
setProps TextType
tt
defaultTo TextType
_  [Element]
ps = [Element]
ps

setProps :: TextType -> [Element]
setProps :: TextType -> [Element]
setProps TextType
tt =
  case TextType
tt of
       TextType
TextNormal       -> [String -> Element
sty String
"p"]
       TextType
TextBold         -> [String -> Element
sty String
"b"]
       TextType
TextItalic       -> [String -> Element
sty String
"i"]
       TextType
TextMonospace    -> [String -> Element
sty String
"p", String -> Element
scr String
"monospace"]
       TextType
TextSansSerif    -> [String -> Element
sty String
"p", String -> Element
scr String
"sans-serif"]
       TextType
TextDoubleStruck -> [String -> Element
sty String
"p", String -> Element
scr String
"double-struck"]
       TextType
TextScript       -> [String -> Element
sty String
"p", String -> Element
scr String
"script"]
       TextType
TextFraktur      -> [String -> Element
sty String
"p", String -> Element
scr String
"fraktur"]
       TextType
TextBoldItalic    -> [String -> Element
sty String
"bi"]
       TextType
TextSansSerifBold -> [String -> Element
sty String
"b", String -> Element
scr String
"sans-serif"]
       TextType
TextBoldScript    -> [String -> Element
sty String
"b", String -> Element
scr String
"script"]
       TextType
TextBoldFraktur   -> [String -> Element
sty String
"b", String -> Element
scr String
"fraktur"]
       TextType
TextSansSerifItalic -> [String -> Element
sty String
"i", String -> Element
scr String
"sans-serif"]
       TextType
TextSansSerifBoldItalic -> [String -> Element
sty String
"bi", String -> Element
scr String
"sans-serif"]
   where sty :: String -> Element
sty String
x = forall t. Node t => String -> String -> t -> Element
mnodeA String
"sty" String
x ()
         scr :: String -> Element
scr String
x = forall t. Node t => String -> String -> t -> Element
mnodeA String
"scr" String
x ()

handleScaledDelims :: [Exp] -> [Exp]
handleScaledDelims :: [Exp] -> [Exp]
handleScaledDelims (x :: Exp
x@(EScaled Rational
scale (ESymbol TeXSymbolType
Open Text
op)) : [Exp]
xs) =
  case forall a. (a -> Bool) -> [a] -> ([a], [a])
break Exp -> Bool
isCloser [Exp]
xs of
    ([Exp]
ys, EScaled Rational
scale' (ESymbol TeXSymbolType
Close Text
cl) : [Exp]
zs) | Rational
scale' forall a. Eq a => a -> a -> Bool
== Rational
scale ->
      Text -> Text -> [InEDelimited] -> Exp
EDelimited Text
op Text
cl (forall a b. (a -> b) -> [a] -> [b]
map forall a b. b -> Either a b
Right [Exp]
ys) forall a. a -> [a] -> [a]
: [Exp]
zs
    ([Exp], [Exp])
_ -> Exp
xforall a. a -> [a] -> [a]
:[Exp]
xs
 where
  isCloser :: Exp -> Bool
isCloser (EScaled Rational
_ (ESymbol TeXSymbolType
Close Text
_)) = Bool
True
  isCloser Exp
_ = Bool
False
handleScaledDelims [Exp]
xs = [Exp]
xs


handleDownup :: DisplayType -> [Exp] -> [Exp]
handleDownup :: DisplayType -> [Exp] -> [Exp]
handleDownup DisplayType
dt (Exp
exp' : [Exp]
xs) =
  case Exp
exp' of
       EOver Bool
convertible Exp
x Exp
y
         | Exp -> Bool
isNary Exp
x  ->
             [Exp] -> Exp
EGrouped [Bool -> Exp -> Exp -> Exp -> Exp
EUnderover Bool
convertible Exp
x Exp
emptyGroup Exp
y, Exp
next] forall a. a -> [a] -> [a]
: [Exp]
rest
         | Bool
convertible Bool -> Bool -> Bool
&& DisplayType
dt forall a. Eq a => a -> a -> Bool
== DisplayType
DisplayInline -> Exp -> Exp -> Exp
ESuper Exp
x Exp
y forall a. a -> [a] -> [a]
: [Exp]
xs
       EUnder Bool
convertible Exp
x Exp
y
         | Exp -> Bool
isNary Exp
x  ->
             [Exp] -> Exp
EGrouped [Bool -> Exp -> Exp -> Exp -> Exp
EUnderover Bool
convertible Exp
x Exp
y Exp
emptyGroup, Exp
next] forall a. a -> [a] -> [a]
: [Exp]
rest
         | Bool
convertible Bool -> Bool -> Bool
&& DisplayType
dt forall a. Eq a => a -> a -> Bool
== DisplayType
DisplayInline -> Exp -> Exp -> Exp
ESub Exp
x Exp
y forall a. a -> [a] -> [a]
: [Exp]
xs
       EUnderover Bool
convertible Exp
x Exp
y Exp
z
         | Exp -> Bool
isNary Exp
x  ->
             [Exp] -> Exp
EGrouped [Bool -> Exp -> Exp -> Exp -> Exp
EUnderover Bool
convertible Exp
x Exp
y Exp
z, Exp
next] forall a. a -> [a] -> [a]
: [Exp]
rest
         | Bool
convertible Bool -> Bool -> Bool
&& DisplayType
dt forall a. Eq a => a -> a -> Bool
== DisplayType
DisplayInline -> Exp -> Exp -> Exp -> Exp
ESubsup Exp
x Exp
y Exp
z forall a. a -> [a] -> [a]
: [Exp]
xs
       ESub Exp
x Exp
y
         | Exp -> Bool
isNary Exp
x  -> [Exp] -> Exp
EGrouped [Exp -> Exp -> Exp -> Exp
ESubsup Exp
x Exp
y Exp
emptyGroup, Exp
next] forall a. a -> [a] -> [a]
: [Exp]
rest
       ESuper Exp
x Exp
y
         | Exp -> Bool
isNary Exp
x  -> [Exp] -> Exp
EGrouped [Exp -> Exp -> Exp -> Exp
ESubsup Exp
x Exp
emptyGroup Exp
y, Exp
next] forall a. a -> [a] -> [a]
: [Exp]
rest
       ESubsup Exp
x Exp
y Exp
z
         | Exp -> Bool
isNary Exp
x  -> [Exp] -> Exp
EGrouped [Exp -> Exp -> Exp -> Exp
ESubsup Exp
x Exp
y Exp
z, Exp
next] forall a. a -> [a] -> [a]
: [Exp]
rest
       Exp
_             -> Exp
exp' forall a. a -> [a] -> [a]
: [Exp]
xs
    where (Exp
next, [Exp]
rest) = case [Exp]
xs of
                              (Exp
t:[Exp]
ts) -> (Exp
t,[Exp]
ts)
                              []     -> (Exp
emptyGroup, [])
          emptyGroup :: Exp
emptyGroup = [Exp] -> Exp
EGrouped []
handleDownup DisplayType
_ []            = []

-- TODO This duplication is ugly and inefficient.  See #92.
handleDownup' :: DisplayType -> [InEDelimited] -> [InEDelimited]
handleDownup' :: DisplayType -> [InEDelimited] -> [InEDelimited]
handleDownup' DisplayType
dt ((Right Exp
exp') : [InEDelimited]
xs) =
  case Exp
exp' of
       EOver Bool
convertible Exp
x Exp
y
         | Exp -> Bool
isNary Exp
x  ->
             forall a b. b -> Either a b
Right ([Exp] -> Exp
EGrouped [Bool -> Exp -> Exp -> Exp -> Exp
EUnderover Bool
convertible Exp
x Exp
emptyGroup Exp
y, Exp
next]) forall a. a -> [a] -> [a]
:
             [InEDelimited]
rest
         | Bool
convertible Bool -> Bool -> Bool
&& DisplayType
dt forall a. Eq a => a -> a -> Bool
== DisplayType
DisplayInline -> forall a b. b -> Either a b
Right (Exp -> Exp -> Exp
ESuper Exp
x Exp
y) forall a. a -> [a] -> [a]
: [InEDelimited]
xs
       EUnder Bool
convertible Exp
x Exp
y
         | Exp -> Bool
isNary Exp
x  ->
             forall a b. b -> Either a b
Right ([Exp] -> Exp
EGrouped [Bool -> Exp -> Exp -> Exp -> Exp
EUnderover Bool
convertible Exp
x Exp
y Exp
emptyGroup, Exp
next]) forall a. a -> [a] -> [a]
:
             [InEDelimited]
rest
         | Bool
convertible Bool -> Bool -> Bool
&& DisplayType
dt forall a. Eq a => a -> a -> Bool
== DisplayType
DisplayInline -> forall a b. b -> Either a b
Right (Exp -> Exp -> Exp
ESub Exp
x Exp
y) forall a. a -> [a] -> [a]
: [InEDelimited]
xs
       EUnderover Bool
convertible Exp
x Exp
y Exp
z
         | Exp -> Bool
isNary Exp
x  ->
             forall a b. b -> Either a b
Right ([Exp] -> Exp
EGrouped [Bool -> Exp -> Exp -> Exp -> Exp
EUnderover Bool
convertible Exp
x Exp
y Exp
z, Exp
next]) forall a. a -> [a] -> [a]
: [InEDelimited]
rest
         | Bool
convertible Bool -> Bool -> Bool
&& DisplayType
dt forall a. Eq a => a -> a -> Bool
== DisplayType
DisplayInline -> forall a b. b -> Either a b
Right (Exp -> Exp -> Exp -> Exp
ESubsup Exp
x Exp
y Exp
z) forall a. a -> [a] -> [a]
: [InEDelimited]
xs
       ESub Exp
x Exp
y
         | Exp -> Bool
isNary Exp
x  -> forall a b. b -> Either a b
Right ([Exp] -> Exp
EGrouped [Exp -> Exp -> Exp -> Exp
ESubsup Exp
x Exp
y Exp
emptyGroup, Exp
next]) forall a. a -> [a] -> [a]
: [InEDelimited]
rest
       ESuper Exp
x Exp
y
         | Exp -> Bool
isNary Exp
x  -> forall a b. b -> Either a b
Right ([Exp] -> Exp
EGrouped [Exp -> Exp -> Exp -> Exp
ESubsup Exp
x Exp
emptyGroup Exp
y, Exp
next]) forall a. a -> [a] -> [a]
: [InEDelimited]
rest
       ESubsup Exp
x Exp
y Exp
z
         | Exp -> Bool
isNary Exp
x  -> forall a b. b -> Either a b
Right ([Exp] -> Exp
EGrouped [Exp -> Exp -> Exp -> Exp
ESubsup Exp
x Exp
y Exp
z, Exp
next]) forall a. a -> [a] -> [a]
: [InEDelimited]
rest
       Exp
_             -> forall a b. b -> Either a b
Right Exp
exp' forall a. a -> [a] -> [a]
: [InEDelimited]
xs
    where (Exp
next, [InEDelimited]
rest) = case [InEDelimited]
xs of
                              (Right Exp
t:[InEDelimited]
ts) -> (Exp
t,[InEDelimited]
ts)
                              [InEDelimited]
_            -> (Exp
emptyGroup, [InEDelimited]
xs)
          emptyGroup :: Exp
emptyGroup = [Exp] -> Exp
EGrouped []
handleDownup' DisplayType
_ [InEDelimited]
xs = [InEDelimited]
xs

showExp :: [Element] -> Exp -> [Element]
showExp :: [Element] -> Exp -> [Element]
showExp [Element]
props Exp
e =
 case Exp
e of
   ENumber Text
x        -> [[Element] -> Text -> Element
str [Element]
props Text
x]
   EGrouped [EUnderover Bool
_ (ESymbol TeXSymbolType
Op Text
s) Exp
y Exp
z, Exp
w] ->
     [[Element] -> String -> Text -> Exp -> Exp -> Exp -> Element
makeNary [Element]
props String
"undOvr" Text
s Exp
y Exp
z Exp
w]
   EGrouped [ESubsup (ESymbol TeXSymbolType
Op Text
s) Exp
y Exp
z, Exp
w] ->
     [[Element] -> String -> Text -> Exp -> Exp -> Exp -> Element
makeNary [Element]
props String
"subSup" Text
s Exp
y Exp
z Exp
w]
   EGrouped []      -> [[Element] -> Text -> Element
str [Element]
props Text
"\x200B"] -- avoid dashed box, see #118
   EGrouped [Exp]
xs      -> forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ([Element] -> Exp -> [Element]
showExp [Element]
props) [Exp]
xs
   EDelimited Text
start Text
end [InEDelimited]
xs ->
                  [ forall t. Node t => String -> t -> Element
mnode String
"d" forall a b. (a -> b) -> a -> b
$ forall t. Node t => String -> t -> Element
mnode String
"dPr"
                               [ forall t. Node t => String -> String -> t -> Element
mnodeA String
"begChr" (Text -> String
T.unpack Text
start) ()
                               , forall t. Node t => String -> String -> t -> Element
mnodeA String
"endChr" (Text -> String
T.unpack Text
end) ()
                               , forall t. Node t => String -> String -> t -> Element
mnodeA String
"sepChr" (Text -> String
T.unpack Text
sepchr) ()
                               , forall t. Node t => String -> t -> Element
mnode String
"grow" () ]
                              forall a. a -> [a] -> [a]
: forall a b. (a -> b) -> [a] -> [b]
map (forall t. Node t => String -> t -> Element
mnode String
"e" forall b c a. (b -> c) -> (a -> b) -> a -> c
. forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ([Element] -> Exp -> [Element]
showExp [Element]
props)) ArrayLine
es
                  ]
      where
       seps :: [Text]
seps = forall a b. [Either a b] -> [a]
lefts [InEDelimited]
xs
       sepchr :: Text
sepchr = case [Text]
seps of
                  []    -> Text
""
                  (Text
s:[Text]
_) -> Text
s
       es :: ArrayLine
es   = forall a b. (a -> b) -> [a] -> [b]
map forall a b. [Either a b] -> [b]
rights forall a b. (a -> b) -> a -> b
$ forall a. (a -> Bool) -> [a] -> [[a]]
splitWhen forall a b. Either a b -> Bool
isLeft [InEDelimited]
xs

   EIdentifier Text
""   -> [[Element] -> Text -> Element
str [Element]
props Text
"\x200B"]  -- 0-width space
                       -- to avoid the dashed box we get otherwise; see #118
   EIdentifier Text
x    -> [[Element] -> Text -> Element
str [Element]
props Text
x]
   EMathOperator Text
x  -> [[Element] -> Text -> Element
str (forall t. Node t => String -> String -> t -> Element
mnodeA String
"sty" String
"p" () forall a. a -> [a] -> [a]
: [Element]
props) Text
x]
   ESymbol TeXSymbolType
ty Text
xs
    | Just (Char
c, Text
xs') <- Text -> Maybe (Char, Text)
T.uncons Text
xs
    , Text -> Bool
T.null Text
xs'
    , Char -> Bool
isSymbol Char
c Bool -> Bool -> Bool
|| Char -> Bool
isPunctuation Char
c
                    -> [[Element] -> Text -> Element
str (TextType -> [Element] -> [Element]
defaultTo TextType
TextNormal [Element]
props) Text
xs]
    | TeXSymbolType
ty forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [TeXSymbolType
Op, TeXSymbolType
Bin, TeXSymbolType
Rel]
                    -> [forall t. Node t => String -> t -> Element
mnode String
"box"
                        [ forall t. Node t => String -> t -> Element
mnode String
"boxPr"
                          [ forall t. Node t => String -> String -> t -> Element
mnodeA String
"opEmu" String
"1" () ]
                        , forall t. Node t => String -> t -> Element
mnode String
"e"
                          [[Element] -> Text -> Element
str (TextType -> [Element] -> [Element]
defaultTo TextType
TextNormal [Element]
props) Text
xs]
                        ]]
    | Bool
otherwise     -> [[Element] -> Text -> Element
str (TextType -> [Element] -> [Element]
defaultTo TextType
TextNormal [Element]
props) Text
xs]
   ESpace Rational
n
     | Rational
n forall a. Ord a => a -> a -> Bool
> Rational
0 Bool -> Bool -> Bool
&& Rational
n forall a. Ord a => a -> a -> Bool
<= Rational
0.17    -> [[Element] -> Text -> Element
str [Element]
props Text
"\x2009"]
     | Rational
n forall a. Ord a => a -> a -> Bool
> Rational
0.17 Bool -> Bool -> Bool
&& Rational
n forall a. Ord a => a -> a -> Bool
<= Rational
0.23 -> [[Element] -> Text -> Element
str [Element]
props Text
"\x2005"]
     | Rational
n forall a. Ord a => a -> a -> Bool
> Rational
0.23 Bool -> Bool -> Bool
&& Rational
n forall a. Ord a => a -> a -> Bool
<= Rational
0.28 -> [[Element] -> Text -> Element
str [Element]
props Text
"\x2004"]
     | Rational
n forall a. Ord a => a -> a -> Bool
> Rational
0.28 Bool -> Bool -> Bool
&& Rational
n forall a. Ord a => a -> a -> Bool
<= Rational
0.5  -> [[Element] -> Text -> Element
str [Element]
props Text
"\x2004"]
     | Rational
n forall a. Ord a => a -> a -> Bool
> Rational
0.5 Bool -> Bool -> Bool
&& Rational
n forall a. Ord a => a -> a -> Bool
<= Rational
1.8   -> [[Element] -> Text -> Element
str [Element]
props Text
"\x2001"]
     | Rational
n forall a. Ord a => a -> a -> Bool
> Rational
1.8               -> [[Element] -> Text -> Element
str [Element]
props Text
"\x2001\x2001"]
     | Bool
otherwise             -> [[Element] -> Text -> Element
str [Element]
props Text
"\x200B"]
       -- this is how the xslt sheet handles all spaces
   EUnder Bool
_ Exp
x (ESymbol TeXSymbolType
TUnder Text
t) | (Char -> Bool) -> Text -> Bool
T.all Char -> Bool
isBarChar Text
t ->
                       [forall t. Node t => String -> t -> Element
mnode String
"bar" [ forall t. Node t => String -> t -> Element
mnode String
"barPr" forall a b. (a -> b) -> a -> b
$
                                        forall t. Node t => String -> String -> t -> Element
mnodeA String
"pos" String
"bot" ()
                                    , forall t. Node t => String -> t -> Element
mnode String
"e" forall a b. (a -> b) -> a -> b
$ [Element] -> Exp -> [Element]
showExp [Element]
props Exp
x ]]
   EOver Bool
_ Exp
x (ESymbol TeXSymbolType
TOver Text
t) | (Char -> Bool) -> Text -> Bool
T.all Char -> Bool
isBarChar Text
t ->
                       [forall t. Node t => String -> t -> Element
mnode String
"bar" [ forall t. Node t => String -> t -> Element
mnode String
"barPr" forall a b. (a -> b) -> a -> b
$
                                        forall t. Node t => String -> String -> t -> Element
mnodeA String
"pos" String
"top" ()
                                    , forall t. Node t => String -> t -> Element
mnode String
"e" forall a b. (a -> b) -> a -> b
$ [Element] -> Exp -> [Element]
showExp [Element]
props Exp
x ]]
   EOver Bool
_ Exp
x (ESymbol TeXSymbolType
st (Text -> String
T.unpack -> String
y))
    | TeXSymbolType
st forall a. Eq a => a -> a -> Bool
== TeXSymbolType
Accent  -> [forall t. Node t => String -> t -> Element
mnode String
"acc" [ forall t. Node t => String -> t -> Element
mnode String
"accPr" [ forall t. Node t => String -> String -> t -> Element
mnodeA String
"chr" String
y () ]
                                    , forall t. Node t => String -> t -> Element
mnode String
"e" forall a b. (a -> b) -> a -> b
$ [Element] -> Exp -> [Element]
showExp [Element]
props Exp
x ]]
    | TeXSymbolType
st forall a. Eq a => a -> a -> Bool
== TeXSymbolType
TUnder  -> [forall t. Node t => String -> t -> Element
mnode String
"groupChr" [ forall t. Node t => String -> t -> Element
mnode String
"groupChrPr"
                                           [ forall t. Node t => String -> String -> t -> Element
mnodeA String
"chr" String
y ()
                                           , forall t. Node t => String -> String -> t -> Element
mnodeA String
"pos" String
"bot" ()
                                           , forall t. Node t => String -> String -> t -> Element
mnodeA String
"vertJc" String
"top" () ]
                                    , forall t. Node t => String -> t -> Element
mnode String
"e" forall a b. (a -> b) -> a -> b
$ [Element] -> Exp -> [Element]
showExp [Element]
props Exp
x ]]
    | TeXSymbolType
st forall a. Eq a => a -> a -> Bool
== TeXSymbolType
TOver   -> [forall t. Node t => String -> t -> Element
mnode String
"groupChr" [ forall t. Node t => String -> t -> Element
mnode String
"groupChrPr"
                                           [ forall t. Node t => String -> String -> t -> Element
mnodeA String
"chr" String
y ()
                                           , forall t. Node t => String -> String -> t -> Element
mnodeA String
"pos" String
"top" ()
                                           , forall t. Node t => String -> String -> t -> Element
mnodeA String
"vertJc" String
"bot" () ]
                                    , forall t. Node t => String -> t -> Element
mnode String
"e" forall a b. (a -> b) -> a -> b
$ [Element] -> Exp -> [Element]
showExp [Element]
props Exp
x ]]
   ESub Exp
x Exp
y         -> [forall t. Node t => String -> t -> Element
mnode String
"sSub" [ forall t. Node t => String -> t -> Element
mnode String
"e" forall a b. (a -> b) -> a -> b
$ [Element] -> Exp -> [Element]
showExp [Element]
props Exp
x
                                     , forall t. Node t => String -> t -> Element
mnode String
"sub" forall a b. (a -> b) -> a -> b
$ [Element] -> Exp -> [Element]
showExp [Element]
props Exp
y]]
   ESuper Exp
x Exp
y       -> [forall t. Node t => String -> t -> Element
mnode String
"sSup" [ forall t. Node t => String -> t -> Element
mnode String
"e" forall a b. (a -> b) -> a -> b
$ [Element] -> Exp -> [Element]
showExp [Element]
props Exp
x
                                     , forall t. Node t => String -> t -> Element
mnode String
"sup" forall a b. (a -> b) -> a -> b
$ [Element] -> Exp -> [Element]
showExp [Element]
props Exp
y]]
   ESubsup Exp
x Exp
y Exp
z    -> [forall t. Node t => String -> t -> Element
mnode String
"sSubSup" [ forall t. Node t => String -> t -> Element
mnode String
"e" forall a b. (a -> b) -> a -> b
$ [Element] -> Exp -> [Element]
showExp [Element]
props Exp
x
                                        , forall t. Node t => String -> t -> Element
mnode String
"sub" forall a b. (a -> b) -> a -> b
$ [Element] -> Exp -> [Element]
showExp [Element]
props Exp
y
                                        , forall t. Node t => String -> t -> Element
mnode String
"sup" forall a b. (a -> b) -> a -> b
$ [Element] -> Exp -> [Element]
showExp [Element]
props Exp
z]]
   EUnder Bool
_ Exp
x Exp
y  -> [forall t. Node t => String -> t -> Element
mnode String
"limLow" [ forall t. Node t => String -> t -> Element
mnode String
"e" forall a b. (a -> b) -> a -> b
$ [Element] -> Exp -> [Element]
showExp [Element]
props Exp
x
                                       , forall t. Node t => String -> t -> Element
mnode String
"lim" forall a b. (a -> b) -> a -> b
$ [Element] -> Exp -> [Element]
showExp [Element]
props Exp
y]]
   EOver Bool
_ Exp
x Exp
y   -> [forall t. Node t => String -> t -> Element
mnode String
"limUpp" [ forall t. Node t => String -> t -> Element
mnode String
"e" forall a b. (a -> b) -> a -> b
$ [Element] -> Exp -> [Element]
showExp [Element]
props Exp
x
                                       , forall t. Node t => String -> t -> Element
mnode String
"lim" forall a b. (a -> b) -> a -> b
$ [Element] -> Exp -> [Element]
showExp [Element]
props Exp
y]]
   EUnderover Bool
c Exp
x Exp
y Exp
z -> [Element] -> Exp -> [Element]
showExp [Element]
props (Bool -> Exp -> Exp -> Exp
EUnder Bool
c (Bool -> Exp -> Exp -> Exp
EOver Bool
c Exp
x Exp
z) Exp
y)
   ESqrt Exp
x       -> [forall t. Node t => String -> t -> Element
mnode String
"rad" [ forall t. Node t => String -> t -> Element
mnode String
"radPr" forall a b. (a -> b) -> a -> b
$ forall t. Node t => String -> String -> t -> Element
mnodeA String
"degHide" String
"1" ()
                                      , forall t. Node t => String -> t -> Element
mnode String
"deg" ()
                                      , forall t. Node t => String -> t -> Element
mnode String
"e" forall a b. (a -> b) -> a -> b
$ [Element] -> Exp -> [Element]
showExp [Element]
props Exp
x]]
   ERoot Exp
i Exp
x     -> [forall t. Node t => String -> t -> Element
mnode String
"rad" [ forall t. Node t => String -> t -> Element
mnode String
"deg" forall a b. (a -> b) -> a -> b
$ [Element] -> Exp -> [Element]
showExp [Element]
props Exp
i
                                 , forall t. Node t => String -> t -> Element
mnode String
"e" forall a b. (a -> b) -> a -> b
$ [Element] -> Exp -> [Element]
showExp [Element]
props Exp
x]]
   EFraction FractionType
ft Exp
x Exp
y -> [[Element] -> FractionType -> Exp -> Exp -> Element
showFraction [Element]
props FractionType
ft Exp
x Exp
y]
   EPhantom Exp
x       -> [forall t. Node t => String -> t -> Element
mnode String
"phant" [ forall t. Node t => String -> t -> Element
mnode String
"phantPr"
                                            [ forall t. Node t => String -> String -> t -> Element
mnodeA String
"show" String
"0" () ]
                                          , forall t. Node t => String -> t -> Element
mnode String
"e" forall a b. (a -> b) -> a -> b
$ [Element] -> Exp -> [Element]
showExp [Element]
props Exp
x]]
   EBoxed   Exp
x       -> [forall t. Node t => String -> t -> Element
mnode String
"borderBox" [ forall t. Node t => String -> t -> Element
mnode String
"e" forall a b. (a -> b) -> a -> b
$ [Element] -> Exp -> [Element]
showExp [Element]
props Exp
x]]
   EScaled Rational
_ Exp
x      -> [Element] -> Exp -> [Element]
showExp [Element]
props Exp
x -- no support for scaler?
   EArray [Alignment]
as [ArrayLine]
ls     -> [[Element] -> [Alignment] -> [ArrayLine] -> Element
makeArray [Element]
props [Alignment]
as [ArrayLine]
ls]
   EText TextType
a Text
s        -> [TextType -> Text -> Element
makeText TextType
a Text
s]
   EStyled TextType
a [Exp]
es     -> forall (t :: * -> *) a b. Foldable t => (a -> [b]) -> t a -> [b]
concatMap ([Element] -> Exp -> [Element]
showExp (TextType -> [Element]
setProps TextType
a)) [Exp]
es

isBarChar :: Char -> Bool
isBarChar :: Char -> Bool
isBarChar Char
c = Char
c forall a. Eq a => a -> a -> Bool
== Char
'\x203E' Bool -> Bool -> Bool
|| Char
c forall a. Eq a => a -> a -> Bool
== Char
'\x00AF' Bool -> Bool -> Bool
||
              Char
c forall a. Eq a => a -> a -> Bool
== Char
'\x0304' Bool -> Bool -> Bool
|| Char
c forall a. Eq a => a -> a -> Bool
== Char
'\x0333' Bool -> Bool -> Bool
||
              Char
c forall a. Eq a => a -> a -> Bool
== Char
'_'

-- | Checks whether an expression marks the start of an nary operator
-- expression. These are different integrals, sums, products, and
-- coproducts.
isNary :: Exp -> Bool
isNary :: Exp -> Bool
isNary (ESymbol TeXSymbolType
Op Text
s) = case Text
s of
  Text
"\x222b" -> Bool
True  -- integral
  Text
"\x222c" -> Bool
True  -- double integral
  Text
"\x222d" -> Bool
True  -- triple integral
  Text
"\x222e" -> Bool
True  -- line integral
  Text
"\x222f" -> Bool
True  -- double line integral
  Text
"\x2230" -> Bool
True  -- triple line integral
  Text
"\x220f" -> Bool
True  -- product
  Text
"\x2210" -> Bool
True  -- coproduct
  Text
"\x2211" -> Bool
True  -- sum
  Text
_        -> Bool
False
isNary Exp
_ = Bool
False

-- Kept as String for Text.XML.Light
makeNary :: [Element] -> String -> T.Text -> Exp -> Exp -> Exp -> Element
makeNary :: [Element] -> String -> Text -> Exp -> Exp -> Exp -> Element
makeNary [Element]
props String
t Text
s Exp
y Exp
z Exp
w =
  forall t. Node t => String -> t -> Element
mnode String
"nary" [ forall t. Node t => String -> t -> Element
mnode String
"naryPr"
                 [ forall t. Node t => String -> String -> t -> Element
mnodeA String
"chr" (Text -> String
T.unpack Text
s) ()
                 , forall t. Node t => String -> String -> t -> Element
mnodeA String
"limLoc" String
t ()
                 , forall t. Node t => String -> String -> t -> Element
mnodeA String
"subHide"
                    (if Exp
y forall a. Eq a => a -> a -> Bool
== [Exp] -> Exp
EGrouped [] then String
"1" else String
"0") ()
                 , forall t. Node t => String -> String -> t -> Element
mnodeA String
"supHide"
                    (if Exp
z forall a. Eq a => a -> a -> Bool
== [Exp] -> Exp
EGrouped [] then String
"1" else String
"0") ()
                 ]
               , forall t. Node t => String -> t -> Element
mnode String
"sub" forall a b. (a -> b) -> a -> b
$ [Element] -> Exp -> [Element]
showExp [Element]
props Exp
y
               , forall t. Node t => String -> t -> Element
mnode String
"sup" forall a b. (a -> b) -> a -> b
$ [Element] -> Exp -> [Element]
showExp [Element]
props Exp
z
               , forall t. Node t => String -> t -> Element
mnode String
"e" forall a b. (a -> b) -> a -> b
$ [Element] -> Exp -> [Element]
showExp [Element]
props Exp
w ]