-- | -- Module : CAS.Dumb.LaTeX.Symbols -- Copyright : (c) Justus SagemΓΌller 2017 -- License : GPL v3 -- -- Maintainer : (@) jsagemue $ uni-koeln.de -- Stability : experimental -- Portability : portable -- -- Orphan instances, allowing to construct CAS syntax trees -- with LaTeX symbols. {-# LANGUAGE OverloadedStrings #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE UnicodeSyntax #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE UndecidableInstances #-} {-# LANGUAGE CPP #-} module CAS.Dumb.LaTeX.Symbols () where import CAS.Dumb.Tree import CAS.Dumb.Symbols import Text.LaTeX import Text.LaTeX.Base.Class import Text.LaTeX.Base.Syntax import Text.LaTeX.Packages.AMSMath import Text.LaTeX.Packages.AMSFonts import qualified Data.Text as Txt import Data.String (IsString(..)) import Data.Char (isAlpha, isUpper, isLower) import Data.Tuple (swap) import Data.Ratio (denominator, numerator) import Numeric.Literals.Decimal import qualified Data.HashMap.Strict as Map import Data.Hashable import Control.Monad import qualified Language.Haskell.TH as Hs instance ASCIISymbols LaTeX where fromASCIISymbol c | isAlpha c = fromString [c] toASCIISymbols (TeXRaw s) = Txt.unpack s instance UnicodeSymbols LaTeX where fromUnicodeSymbol c | Just lc <- Map.lookup c mappingFromUnicode = lc | otherwise = error $ "Unicode symbol '"++[c]++"' not supported in LaTeX expressions." toUnicodeSymbols lc | Just c <- Map.lookup lc mappingToUnicode = [c] | lc==mempty = "" | otherwise = "γ€Š"++Txt.unpack(render lc)++"》" mappingFromUnicode :: Map.HashMap Char LaTeX mappingToUnicode :: Map.HashMap LaTeX Char InvertibleMap mappingFromUnicode mappingToUnicode = mapToLaTeXWith id "π‘Žπ‘π‘π‘‘π‘’π‘“π‘”β„Žπ‘–π‘—π‘˜π‘™π‘šπ‘›π‘œπ‘π‘žπ‘Ÿπ‘ π‘‘π‘’π‘£π‘€π‘₯𝑦𝑧" "abcdefghijklmnopqrstuvwxyz" <|> mapToLaTeXWith mathbf ['𝐚'..'𝐳'] ['a'..'z'] #if __GLASGOW_HASKELL__ > 802 <|> mapToLaTeXWith id ['𝐴'..'𝑍'] ['A'..'Z'] <|> mapToLaTeXWith mathbf ['𝐀'..'𝐙'] ['A'..'Z'] <|> mapToLaTeXWith mathbb "β„‚β„β„šβ„β„€" "CHQRZ" <|> mapToLaTeXWith mathcal ['𝓐'..'𝓩'] ['A'..'Z'] <|> mapToLaTeXWith mathfrak "π”„π”…β„­π”‡π”ˆπ”‰π”Šβ„Œβ„‘π”π”Žπ”π”π”‘π”’π”“π””β„œπ”–π”—π”˜π”™π”šπ”›π”œ" "ABCDEFGHIJKLMNOPQRSTUVWXY" #endif <|> fromAssocList (zip ['Ξ±', 'Ξ²', 'Ξ³', 'Ξ΄', 'Ξ΅', 'ΞΆ', 'Ξ·','ΞΈ', 'Ο‘', 'ΞΉ', 'ΞΊ', 'Ξ»' ] [alpha,beta,gamma,delta,varepsilon,zeta,eta,theta,vartheta,iota,kappa,lambda]) <|> fromAssocList (zip ['ΞΌ','Ξ½','ΞΎ','Ο€','ρ','Ο±', 'Οƒ', 'Ο‚', 'Ο„','Ο…', 'Ο•','Ο†', 'Ο‡','ψ', 'Ο‰' ] [mu, nu, xi, pi, rho,varrho,sigma,varsigma,tau,upsilon,phi,varphi,chi,psi,omega]) #if __GLASGOW_HASKELL__ > 802 <|> fromAssocList (zip ['Ξ“', 'Ξ”', 'Θ', 'Ξ›', 'Ξ','Ξ ','Ξ£', 'Ξ₯', 'Ξ¦', 'Ξ¨', 'Ξ©' ] [gammau,deltau,thetau,lambdau,xiu,piu,sigmau,upsilonu,phiu,psiu,omegau]) #endif <|> fromAssocList (zip ['+', '-', '*', 'Β±', 'βˆ“' ] ["+", "-", raw"{\\cdot}", raw"{\\pm}", raw"{\\mp}"]) remapWith :: (a->b) -> [a] -> [a] -> [(a, b)] remapWith f = zipWith (\lc rc -> (lc, f rc)) mapToLaTeXWith :: (LaTeX->LaTeX) -> [Char] -> [Char] -> InvertibleMap Char LaTeX mapToLaTeXWith f l r = fromAssocList $ remapWith (f . fromString . pure) l r data InvertibleMap a b = InvertibleMap { fwdMapping :: Map.HashMap a b , revMapping :: Map.HashMap b a } fromAssocList :: (Hashable a, Hashable b, Eq a, Eq b) => [(a,b)] -> InvertibleMap a b fromAssocList assocs = InvertibleMap (Map.fromList assocs) (Map.fromList $ map swap assocs) infixl 3 <|> (<|>) :: (Hashable a, Hashable b, Eq a, Eq b) => InvertibleMap a b -> InvertibleMap a b -> InvertibleMap a b InvertibleMap af ar<|>InvertibleMap bf br = InvertibleMap (Map.union af bf) (Map.union ar br) encapsulation :: l -> l -> (CAS' Ξ³ (Infix l) (Encapsulation l) (SymbolD Οƒ l)) -> (CAS' Ξ³ (Infix l) (Encapsulation l) (SymbolD Οƒ l)) encapsulation l r = Function $ Encapsulation False True l r latexFunction :: LaTeXC l => Text -> (CAS' Ξ³ (Infix l) (Encapsulation l) (SymbolD Οƒ l)) -> (CAS' Ξ³ (Infix l) (Encapsulation l) (SymbolD Οƒ l)) latexFunction f = Function $ Encapsulation True False (raw $ f<>"{") (raw "}") instance βˆ€ Οƒ Ξ³ . (SymbolClass Οƒ, SCConstraint Οƒ LaTeX) => Num (CAS' Ξ³ (Infix LaTeX) (Encapsulation LaTeX) (SymbolD Οƒ LaTeX)) where fromInteger n | n<0 = negate . fromInteger $ -n | otherwise = Symbol $ NatSymbol n (+) = chainableInfixL (==plusOp) plusOp where fcs = fromCharSymbol ([]::[Οƒ]) plusOp = Infix (Hs.Fixity 6 Hs.InfixL) $ fcs '+' (*) = chainableInfixL (==mulOp) mulOp where fcs = fromCharSymbol ([]::[Οƒ]) mulOp = Infix (Hs.Fixity 7 Hs.InfixL) $ fcs '*' (-) = symbolInfix (Infix (Hs.Fixity 6 Hs.InfixL) $ fcs '-') where fcs = fromCharSymbol ([]::[Οƒ]) abs = encapsulation (raw "\\left|") (raw "\\right|") signum = latexFunction "\\signum" negate = Operator (Infix (Hs.Fixity 6 Hs.InfixL) $ fcs '-') . Symbol $ StringSymbol mempty where fcs = fromCharSymbol ([]::[Οƒ]) instance βˆ€ Οƒ Ξ³ . (SymbolClass Οƒ, SCConstraint Οƒ LaTeX) => Fractional (CAS' Ξ³ (Infix LaTeX) (Encapsulation LaTeX) (SymbolD Οƒ LaTeX)) where fromRational n = case fromRational n of n:%d -> fromIntegral n / fromIntegral d Scientific pc acs e -> let m = Symbol (StringSymbol . fromString $ show pc++ if null acs then "" else "."++(show=< Floating (CAS' Ξ³ (Infix LaTeX) (Encapsulation LaTeX) (SymbolD Οƒ LaTeX)) where pi = Symbol $ StringSymbol pi_ sqrt = encapsulation (raw "\\sqrt{") (raw "}") a ** b = Operator (Infix (Hs.Fixity 8 Hs.InfixR) mempty) a (encapsulation (raw "^{") (raw "}") b) logBase b a = Operator (Infix (Hs.Fixity 10 Hs.InfixL) mempty) (encapsulation (raw "\\log_{") (raw "}") b) a exp = latexFunction "\\exp" log = latexFunction "\\log" sin = latexFunction "\\sin" cos = latexFunction "\\cos" tan = latexFunction "\\tan" asin = latexFunction "\\asin" acos = latexFunction "\\acos" atan = latexFunction "\\atan" sinh = latexFunction "\\sinh" cosh = latexFunction "\\cosh" tanh = latexFunction "\\tanh" asinh = latexFunction "\\asinh" acosh = latexFunction "\\acosh" atanh = latexFunction "\\atanh" instance Eq (Encapsulation LaTeX) where Encapsulation _ _ l r == Encapsulation _ _ l' r' = l==l' && r==r'