-- | -- Module : CAS.Dumb.Symbols.Unicode.MathLatin_RomanGreek__BopomofoGaps -- Copyright : (c) Justus Sagemรผller 2017 -- License : GPL v3 -- -- Maintainer : (@) jsagemue $ uni-koeln.de -- Stability : experimental -- Portability : portable -- -- This module contains a collection of symbols that should be sufficient for usage -- in most algebra applications. It avoids polluting the namespace with single-letter -- variables (which are often used as local variables, leading to shadowing issues), -- by replacing also the Latin letters with less common Unicode symbols. If you're -- not concerned with this and prefer symbols that can directly be entered on any -- Western keyboard, use the "CAS.Dumb.Symbols.ASCII" module instead. {-# LANGUAGE PatternSynonyms #-} {-# LANGUAGE FlexibleInstances #-} {-# LANGUAGE ScopedTypeVariables #-} {-# LANGUAGE TypeFamilies #-} {-# LANGUAGE UnicodeSyntax #-} {-# LANGUAGE TemplateHaskell #-} {-# LANGUAGE CPP #-} module CAS.Dumb.Symbols.Unicode.MathLatin_RomanGreek__BopomofoGaps ( module CAS.Dumb.Symbols , Symbol, Expression, Pattern -- * โ€œConstant variableโ€ symbols -- ** Lowercase letters -- $UnicodeMathSymHelp -- *** Italic Latin , ๐‘Ž,๐‘,๐‘,๐‘‘,๐‘’,๐‘“,๐‘”,โ„Ž,๐‘–,๐‘—,๐‘˜,๐‘™,๐‘š,๐‘›,๐‘œ,๐‘,๐‘ž,๐‘Ÿ,๐‘ ,๐‘ก,๐‘ข,๐‘ฃ,๐‘ค,๐‘ฅ,๐‘ฆ,๐‘ง -- *** Bold , ๐š,๐›,๐œ,๐,๐ž,๐Ÿ,๐ ,๐ก,๐ข,๐ฃ,๐ค,๐ฅ,๐ฆ,๐ง,๐จ,๐ฉ,๐ช,๐ซ,๐ฌ,๐ญ,๐ฎ,๐ฏ,๐ฐ,๐ฑ,๐ฒ,๐ณ -- *** Greek , ฮฑ,ฮฒ,ฮณ,ฮด,ฮต,ฮถ,ฮท,ฮธ,ฯ‘,ฮน,ฮบ,ฮป,ฮผ,ฮฝ,ฮพ,ฮฟ,ฯ€,ฯ,ฯฑ,ฯƒ,ฯ‚,ฯ„,ฯ…,ฯ•,ฯ†,ฯ‡,ฯˆ,ฯ‰ -- ** Uppercase letters -- $uppercaseCaveat #if __GLASGOW_HASKELL__ > 801 -- *** Italic , pattern ๐ด, pattern ๐ต, pattern ๐ถ, pattern ๐ท, pattern ๐ธ, pattern ๐น, pattern ๐บ, pattern ๐ป, pattern ๐ผ, pattern ๐ฝ, pattern ๐พ, pattern ๐ฟ, pattern ๐‘€, pattern ๐‘, pattern ๐‘‚, pattern ๐‘ƒ, pattern ๐‘„, pattern ๐‘…, pattern ๐‘†, pattern ๐‘‡, pattern ๐‘ˆ, pattern ๐‘‰, pattern ๐‘Š, pattern ๐‘‹, pattern ๐‘Œ, pattern ๐‘ -- *** Bold , pattern ๐€, pattern ๐, pattern ๐‚, pattern ๐ƒ, pattern ๐„, pattern ๐…, pattern ๐†, pattern ๐‡, pattern ๐ˆ, pattern ๐‰, pattern ๐Š, pattern ๐‹, pattern ๐Œ, pattern ๐, pattern ๐Ž, pattern ๐, pattern ๐, pattern ๐‘, pattern ๐’, pattern ๐“, pattern ๐”, pattern ๐•, pattern ๐–, pattern ๐—, pattern ๐˜, pattern ๐™ -- *** Blackboard (LaTeX subset) , pattern โ„‚, pattern โ„, pattern โ„•, pattern โ„š, pattern โ„, pattern โ„ค -- *** Blackboard (nonstandard) , pattern ๐”ธ, pattern ๐”น, pattern ๐”ป, pattern ๐”ผ, pattern ๐”ฝ, pattern ๐”พ, pattern ๐•€, pattern ๐•, pattern ๐•‚, pattern ๐•ƒ, pattern ๐•„, pattern ๐•†, pattern ๐•Š, pattern ๐•‹, pattern ๐•Œ, pattern ๐•, pattern ๐•Ž, pattern ๐•, pattern ๐• -- *** Script , pattern ๐’œ, pattern โ„ฌ, pattern ๐’ž, pattern ๐’Ÿ, pattern โ„ฐ, pattern โ„ฑ, pattern ๐’ข, pattern โ„‹, pattern โ„, pattern ๐’ฅ, pattern ๐’ฆ, pattern โ„’, pattern โ„ณ, pattern ๐’ฉ, pattern ๐’ช, pattern ๐’ซ, pattern ๐’ฌ, pattern โ„›, pattern ๐’ฎ, pattern ๐’ฏ, pattern ๐’ฐ, pattern ๐’ฑ, pattern ๐’ฒ, pattern ๐’ณ, pattern ๐’ด, pattern ๐’ต -- *** Calligraphic / bold-script , pattern ๐“, pattern ๐“‘, pattern ๐“’, pattern ๐““, pattern ๐“”, pattern ๐“•, pattern ๐“–, pattern ๐“—, pattern ๐“˜, pattern ๐“™, pattern ๐“š, pattern ๐“›, pattern ๐“œ, pattern ๐“, pattern ๐“ž, pattern ๐“Ÿ, pattern ๐“ , pattern ๐“ก, pattern ๐“ข, pattern ๐“ฃ, pattern ๐“ค, pattern ๐“ฅ, pattern ๐“ฆ, pattern ๐“ง, pattern ๐“จ, pattern ๐“ฉ -- *** Fraktur , pattern ๐”„, pattern ๐”…, pattern โ„ญ, pattern ๐”‡, pattern ๐”ˆ, pattern ๐”‰, pattern ๐”Š, pattern โ„Œ, pattern โ„‘, pattern ๐”, pattern ๐”Ž, pattern ๐”, pattern ๐”, pattern ๐”‘, pattern ๐”’, pattern ๐”“, pattern ๐””, pattern โ„œ, pattern ๐”–, pattern ๐”—, pattern ๐”˜, pattern ๐”™, pattern ๐”š, pattern ๐”›, pattern ๐”œ -- *** Greek (LaTeX subset) -- $greekUppercaseLaTeXInfo , pattern ฮ“, pattern ฮ”, pattern ฮ˜, pattern ฮ›, pattern ฮž, pattern ฮ , pattern ฮฃ, pattern ฮฅ, pattern ฮฆ, pattern ฮจ, pattern ฮฉ -- *** Greek (Latin-lookalike) , pattern ฮ‘, pattern ฮ’, pattern ฮ•, pattern ฮ–, pattern ฮ—, pattern ฮ™, pattern ฮš, pattern ฮœ, pattern ฮ, pattern ฮŸ, pattern ฮก, pattern ฮค, pattern ฮง #endif -- * Pattern-matching variable symbols -- $BopomofoHelp , ใ„…,ใ„†,ใ„‡,ใ„ˆ,ใ„‰,ใ„Š,ใ„‹,ใ„Œ,ใ„,ใ„Ž,ใ„,ใ„,ใ„‘,ใ„’,ใ„“,ใ„”,ใ„•,ใ„–,ใ„—,ใ„˜,ใ„™,ใ„š,ใ„›,ใ„œ,ใ„,ใ„ž,ใ„Ÿ,ใ„ ,ใ„ก,ใ„ข,ใ„ฃ,ใ„ค,ใ„ฅ,ใ„ฆ,ใ„ง,ใ„จ,ใ„ฉ,ใ„ช,ใ„ซ,ใ„ฌ -- * Auxiliary , Expression' ) where import CAS.Dumb.Tree import CAS.Dumb.Symbols hiding ((&~~!), (&~~:), continueExpr) import CAS.Dumb.Symbols.PatternGenerator import Data.Void import Control.Arrow data Unicode_MathLatin_RomanGreek__BopomofoGaps instance SymbolClass Unicode_MathLatin_RomanGreek__BopomofoGaps where type SCConstraint Unicode_MathLatin_RomanGreek__BopomofoGaps = UnicodeSymbols fromCharSymbol _ = fromUnicodeSymbol type Symbol = SymbolD Unicode_MathLatin_RomanGreek__BopomofoGaps type Expression' ฮณ sยฒ sยน c = CAS' ฮณ sยฒ sยน (Symbol c) type Expression c = Expression' Void (Infix c) (Encapsulation c) c type Pattern c = Expression' GapId (Infix c) (Encapsulation c) c -- $UnicodeMathSymHelp -- Unicode mathematical italic letters. Italic is the default way maths symbols appear in -- e.g. LaTeX-rendered documents, thus it makes sense to use them here. makeSymbols ''Expression' "๐‘Ž๐‘๐‘๐‘‘๐‘’๐‘“๐‘”โ„Ž๐‘–๐‘—๐‘˜๐‘™๐‘š๐‘›๐‘œ๐‘๐‘ž๐‘Ÿ๐‘ ๐‘ก๐‘ข๐‘ฃ๐‘ค๐‘ฅ๐‘ฆ๐‘ง" makeSymbols ''Expression' ['๐š'..'๐ณ'] makeSymbols ''Expression' "ฮฑฮฒฮณฮดฮตฮถฮทฮธฯ‘ฮนฮบฮปฮผฮฝฮพฮฟฯ€ฯฯฑฯƒฯ‚ฯ„ฯ…ฯ•ฯ†ฯ‡ฯˆฯ‰" -- $uppercaseCaveat -- These are only available in GHC>8.2. The ability to use uppercase letters as variables -- hinges on a hack using GHC's still recent -- feature. -- -- You can use the "CAS.Dumb.Symbols.Unicode.MathLatin_RomanGreek.Qualified" -- module if this causes you any trouble; there, all symbols are prefixed with -- @sym@ and therefore the uppercase ones are still normal lowercase names -- in the Haskell code. #if __GLASGOW_HASKELL__ > 801 makeSymbols ''Expression' ['๐ด'..'๐‘'] makeSymbols ''Expression' ['๐€'..'๐™'] makeSymbols ''Expression' "๐”ธ๐”นโ„‚๐”ป๐”ผ๐”ฝ๐”พโ„๐•€๐•๐•‚๐•ƒ๐•„โ„•๐•†โ„šโ„๐•Š๐•‹๐•Œ๐•๐•Ž๐•๐•โ„ค" makeSymbols ''Expression' "๐’œโ„ฌ๐’ž๐’Ÿโ„ฐโ„ฑ๐’ขโ„‹โ„๐’ฅ๐’ฆโ„’โ„ณ๐’ฉ๐’ช๐’ซ๐’ฌโ„›๐’ฎ๐’ฏ๐’ฐ๐’ฑ๐’ฒ๐’ณ๐’ด๐’ต" makeSymbols ''Expression' ['๐“'..'๐“ฉ'] makeSymbols ''Expression' "๐”„๐”…โ„ญ๐”‡๐”ˆ๐”‰๐”Šโ„Œโ„‘๐”๐”Ž๐”๐”๐”‘๐”’๐”“๐””โ„œ๐”–๐”—๐”˜๐”™๐”š๐”›๐”œ" -- $greekUppercaseLaTeXInfo -- These are the uppercase greek letters that don't have latin lookalikes. Only these -- are supported in LaTeX, so for doing maths it's probably best to stick to this subset. makeSymbols ''Expression' $ ['ฮ‘'..'ฮก']++['ฮฃ'..'ฮฉ'] #endif -- $BopomofoHelp -- Using a non-European alphabet such as Bopomofo for 'Gap's (which are always only -- temporary placeholders that, unlike 'Symbol's, should never appear in any program -- output) has the advantage of keeping the namespace clean and avoiding ambiguities. -- -- Most of these symbols can easily be entered as -- , -- namely by combining a (latin) letter with the number 4. For instance, @ctrl-k e 4@ -- generates the symbol @ใ„œ U+311C BOPOMOFO LETTER E@. ใ„…,ใ„†,ใ„‡,ใ„ˆ,ใ„‰,ใ„Š,ใ„‹,ใ„Œ,ใ„,ใ„Ž,ใ„,ใ„,ใ„‘,ใ„’,ใ„“,ใ„”,ใ„•,ใ„–,ใ„—,ใ„˜,ใ„™,ใ„š,ใ„›,ใ„œ,ใ„,ใ„ž,ใ„Ÿ ,ใ„ ,ใ„ก,ใ„ข,ใ„ฃ,ใ„ค,ใ„ฅ,ใ„ฆ,ใ„ง,ใ„จ,ใ„ฉ,ใ„ช,ใ„ซ,ใ„ฌ:: CAS' GapId sยฒ sยน sโฐ [ใ„…,ใ„†,ใ„‡,ใ„ˆ,ใ„‰,ใ„Š,ใ„‹,ใ„Œ,ใ„,ใ„Ž,ใ„,ใ„,ใ„‘,ใ„’,ใ„“,ใ„”,ใ„•,ใ„–,ใ„—,ใ„˜,ใ„™,ใ„š,ใ„›,ใ„œ,ใ„,ใ„ž,ใ„Ÿ ,ใ„ ,ใ„ก,ใ„ข,ใ„ฃ,ใ„ค,ใ„ฅ,ใ„ฆ,ใ„ง,ใ„จ,ใ„ฉ,ใ„ช,ใ„ซ,ใ„ฌ] = Gap . fromEnum <$> ['ใ„…'..'ใ„ฌ'] instance UnicodeSymbols c => Show (Expression c) where showsPrec = showsPrecUnicodeSymbol instance โˆ€ c . UnicodeSymbols c => Show (Pattern c) where showsPrec p = showsPrecUnicodeSymbol p . purgeGaps where purgeGaps (Symbol s) = Symbol s purgeGaps (Function f e) = Function f $ purgeGaps e purgeGaps (Operator o x y) = Operator o (purgeGaps x) (purgeGaps y) purgeGaps (OperatorChain x ys) = OperatorChain (purgeGaps x) (second purgeGaps<$>ys) purgeGaps (Gap gid) = Symbol (PrimitiveSymbol (toEnum gid)) :: Expression c