-- | Possibly indexed symbols. module Math.FreeModule.Symbol where -------------------------------------------------------------------------------- import Data.Set (Set) import qualified Data.Set as Set -------------------------------------------------------------------------------- data Symbol = Symbol { _name :: String , _index :: Maybe Int } deriving (Eq,Ord,Show) -------------------------------------------------------------------------------- -- | Shows the symbols in @\"alpha[5]\"@ style showSymbol :: Symbol -> String showSymbol (Symbol name idx) = case idx of Just j -> name ++ "[" ++ show j ++ "]" Nothing -> name -- | Shows the symbols in @\"alpha5\"@ style showSymbol' :: Symbol -> String showSymbol' (Symbol name idx) = case idx of Just j -> name ++ show j Nothing -> name -- | Shows the symbols in @\"\\alpha_{5}\"@ style showSymbolLatex :: Symbol -> String showSymbolLatex (Symbol name idx) = case idx of Just j -> name' ++ "_{" ++ show j ++ "}" Nothing -> name' where name' = if Set.member name latexGreek then '\\' : name else name -------------------------------------------------------------------------------- latexGreek :: Set String latexGreek = Set.fromList (latexSmallGreek ++ latexCapitalGreek) latexSmallGreek :: [String] latexSmallGreek = [ "alpha" , "beta" , "gamma" , "delta" , "epsilon" , "zeta" , "eta" , "theta" , "iota" , "kappa" , "lambda" , "mu" , "nu" , "xi" , "pi" , "rho" , "sigma" , "tau" , "upsilon" , "phi" , "chi" , "psi" , "omega" ] latexCapitalGreek :: [String] latexCapitalGreek = [ "Gamma" , "Delta" , "Theta" , "Lambda" , "Xi" , "Pi" , "Sigma" , "Upsilon" , "Phi" , "Psi" ] --------------------------------------------------------------------------------