{-# LANGUAGE OverloadedStrings #-}
{-
Copyright (C) 2014 Matthew Pickering <matthewtpickering@gmail.com>

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
-}
{- |
Dictionary of operators to MathML attributes as specified by the W3C standard.

The original file can be downloaded from <http://www.w3.org/TR/xml-entity-names/#source here>
-}

module Text.TeXMath.Readers.MathML.MMLDict (getMathMLOperator, operators) where

import Text.TeXMath.Types
import qualified Data.Map as M
import qualified Data.Text as T
import Data.Monoid (First(..))

dict :: M.Map (T.Text, FormType) Operator
dict :: Map (Text, FormType) Operator
dict = forall k a. Ord k => [(k, a)] -> Map k a
M.fromList (forall a b. (a -> b) -> [a] -> [b]
map (\Operator
o -> ((Operator -> Text
oper Operator
o, Operator -> FormType
form Operator
o), Operator
o)) [Operator]
operators)

-- | Tries to find the 'Operator' record based on a given position. If
-- there is no exact match then the positions will be tried in the
-- following order (Infix, Postfix, Prefix) with the first match (if any) being returned.
getMathMLOperator :: T.Text -> FormType -> Maybe Operator
getMathMLOperator :: Text -> FormType -> Maybe Operator
getMathMLOperator Text
s FormType
p =
  forall a. First a -> Maybe a
getFirst forall a b. (a -> b) -> a -> b
$ forall a. Monoid a => [a] -> a
mconcat forall a b. (a -> b) -> a -> b
$ (forall a b. (a -> b) -> [a] -> [b]
map (\FormType
x -> forall a. Maybe a -> First a
First forall a b. (a -> b) -> a -> b
$ forall k a. Ord k => k -> Map k a -> Maybe a
M.lookup (Text
s, FormType
x) Map (Text, FormType) Operator
dict) [FormType]
lookupOrder)
  where
    lookupOrder :: [FormType]
lookupOrder = [FormType
p, FormType
FInfix, FormType
FPostfix, FormType
FPrefix]

-- | A table of all operators as defined by the MathML operator dictionary.
operators :: [Operator]
operators :: [Operator]
operators =
  [ Operator {oper :: Text
oper = Text
"!", description :: Text
description = Text
"EXCLAMATION MARK", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
810, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"!!", description :: Text
description = Text
"MULTIPLE CHARACTER OPERATOR: !!", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
810, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"!=", description :: Text
description = Text
"MULTIPLE CHARACTER OPERATOR: !=", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\"", description :: Text
description = Text
"QUOTATION MARK", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"%", description :: Text
description = Text
"PERCENT SIGN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
640, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"&", description :: Text
description = Text
"AMPERSAND", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"&&", description :: Text
description = Text
"MULTIPLE CHARACTER OPERATOR: &&", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
200, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"'", description :: Text
description = Text
"APOSTROPHE", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"(", description :: Text
description = Text
"LEFT PARENTHESIS", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
")", description :: Text
description = Text
"RIGHT PARENTHESIS", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"*", description :: Text
description = Text
"ASTERISK", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
390, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"**", description :: Text
description = Text
"MULTIPLE CHARACTER OPERATOR: **", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
780, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"*=", description :: Text
description = Text
"MULTIPLE CHARACTER OPERATOR: *=", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"+", description :: Text
description = Text
"PLUS SIGN", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
275, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"+", description :: Text
description = Text
"PLUS SIGN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
275, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"++", description :: Text
description = Text
"MULTIPLE CHARACTER OPERATOR: ++", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"+=", description :: Text
description = Text
"MULTIPLE CHARACTER OPERATOR: +=", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
",", description :: Text
description = Text
"COMMA", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
40, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = [Text
"separator"]}
  , Operator {oper :: Text
oper = Text
"-", description :: Text
description = Text
"HYPHEN-MINUS", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
275, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"-", description :: Text
description = Text
"HYPHEN-MINUS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
275, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"--", description :: Text
description = Text
"MULTIPLE CHARACTER OPERATOR: --", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"-=", description :: Text
description = Text
"MULTIPLE CHARACTER OPERATOR: -=", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"->", description :: Text
description = Text
"MULTIPLE CHARACTER OPERATOR: ->", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
90, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
".", description :: Text
description = Text
"FULL STOP", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
390, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"..", description :: Text
description = Text
"MULTIPLE CHARACTER OPERATOR: ..", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
100, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"...", description :: Text
description = Text
"MULTIPLE CHARACTER OPERATOR: ...", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
100, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"/", description :: Text
description = Text
"SOLIDUS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
660, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"//", description :: Text
description = Text
"MULTIPLE CHARACTER OPERATOR: //", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
820, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"/=", description :: Text
description = Text
"MULTIPLE CHARACTER OPERATOR: /=", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
":", description :: Text
description = Text
"COLON", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
100, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
":=", description :: Text
description = Text
"MULTIPLE CHARACTER OPERATOR: :=", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
";", description :: Text
description = Text
"SEMICOLON", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
30, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = [Text
"separator"]}
  , Operator {oper :: Text
oper = Text
"<", description :: Text
description = Text
"LESS-THAN SIGN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
245, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"<=", description :: Text
description = Text
"MULTIPLE CHARACTER OPERATOR: <=", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
241, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"<>", description :: Text
description = Text
"MULTIPLE CHARACTER OPERATOR: <>", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
780, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"=", description :: Text
description = Text
"EQUALS SIGN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"==", description :: Text
description = Text
"MULTIPLE CHARACTER OPERATOR: ==", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
">", description :: Text
description = Text
"GREATER-THAN SIGN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
243, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
">=", description :: Text
description = Text
"MULTIPLE CHARACTER OPERATOR: >=", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
243, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"?", description :: Text
description = Text
"QUESTION MARK", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
835, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"@", description :: Text
description = Text
"COMMERCIAL AT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
825, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"[", description :: Text
description = Text
"LEFT SQUARE BRACKET", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\\", description :: Text
description = Text
"REVERSE SOLIDUS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
650, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"]", description :: Text
description = Text
"RIGHT SQUARE BRACKET", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"^", description :: Text
description = Text
"CIRCUMFLEX ACCENT", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"^", description :: Text
description = Text
"CIRCUMFLEX ACCENT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
780, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"_", description :: Text
description = Text
"LOW LINE", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"_", description :: Text
description = Text
"LOW LINE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
900, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"`", description :: Text
description = Text
"GRAVE ACCENT", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"{", description :: Text
description = Text
"LEFT CURLY BRACKET", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"|", description :: Text
description = Text
"VERTICAL LINE", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"|", description :: Text
description = Text
"VERTICAL LINE", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"|", description :: Text
description = Text
"VERTICAL LINE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
2, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"stretchy",Text
"symmetric",Text
"fence"]}
  , Operator {oper :: Text
oper = Text
"||", description :: Text
description = Text
"MULTIPLE CHARACTER OPERATOR: ||", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"||", description :: Text
description = Text
"MULTIPLE CHARACTER OPERATOR: ||", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"||", description :: Text
description = Text
"MULTIPLE CHARACTER OPERATOR: ||", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
2, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"stretchy",Text
"symmetric",Text
"fence"]}
  , Operator {oper :: Text
oper = Text
"|||", description :: Text
description = Text
"MULTIPLE CHARACTER OPERATOR: |||", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"|||", description :: Text
description = Text
"MULTIPLE CHARACTER OPERATOR: |||", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"|||", description :: Text
description = Text
"MULTIPLE CHARACTER OPERATOR: |||", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
2, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"stretchy",Text
"symmetric",Text
"fence"]}
  , Operator {oper :: Text
oper = Text
"}", description :: Text
description = Text
"RIGHT CURLY BRACKET", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"~", description :: Text
description = Text
"TILDE", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\168", description :: Text
description = Text
"DIAERESIS", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\170", description :: Text
description = Text
"FEMININE ORDINAL INDICATOR", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\172", description :: Text
description = Text
"NOT SIGN", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
680, lspace :: Int
lspace = Int
2, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\175", description :: Text
description = Text
"MACRON", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\176", description :: Text
description = Text
"DEGREE SIGN", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\177", description :: Text
description = Text
"PLUS-MINUS SIGN", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
275, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\177", description :: Text
description = Text
"PLUS-MINUS SIGN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
275, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\178", description :: Text
description = Text
"SUPERSCRIPT TWO", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\179", description :: Text
description = Text
"SUPERSCRIPT THREE", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\180", description :: Text
description = Text
"ACUTE ACCENT", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\183", description :: Text
description = Text
"MIDDLE DOT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
400, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\184", description :: Text
description = Text
"CEDILLA", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\185", description :: Text
description = Text
"SUPERSCRIPT ONE", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\186", description :: Text
description = Text
"MASCULINE ORDINAL INDICATOR", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\215", description :: Text
description = Text
"MULTIPLICATION SIGN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
390, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\247", description :: Text
description = Text
"DIVISION SIGN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
660, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\710", description :: Text
description = Text
"MODIFIER LETTER CIRCUMFLEX ACCENT", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\711", description :: Text
description = Text
"CARON", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\713", description :: Text
description = Text
"MODIFIER LETTER MACRON", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\714", description :: Text
description = Text
"MODIFIER LETTER ACUTE ACCENT", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\715", description :: Text
description = Text
"MODIFIER LETTER GRAVE ACCENT", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\717", description :: Text
description = Text
"MODIFIER LETTER LOW MACRON", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\728", description :: Text
description = Text
"BREVE", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\729", description :: Text
description = Text
"DOT ABOVE", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\730", description :: Text
description = Text
"RING ABOVE", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\732", description :: Text
description = Text
"SMALL TILDE", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\733", description :: Text
description = Text
"DOUBLE ACUTE ACCENT", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\759", description :: Text
description = Text
"MODIFIER LETTER LOW TILDE", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\770", description :: Text
description = Text
"COMBINING CIRCUMFLEX ACCENT", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\785", description :: Text
description = Text
"COMBINING INVERTED BREVE", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\1014", description :: Text
description = Text
"GREEK REVERSED LUNATE EPSILON SYMBOL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
110, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8214", description :: Text
description = Text
"DOUBLE VERTICAL LINE", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"fence",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8214", description :: Text
description = Text
"DOUBLE VERTICAL LINE", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"fence",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8216", description :: Text
description = Text
"LEFT SINGLE QUOTATION MARK", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
10, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"fence",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\8217", description :: Text
description = Text
"RIGHT SINGLE QUOTATION MARK", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
10, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"fence",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\8218", description :: Text
description = Text
"SINGLE LOW-9 QUOTATION MARK", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\8219", description :: Text
description = Text
"SINGLE HIGH-REVERSED-9 QUOTATION MARK", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\8220", description :: Text
description = Text
"LEFT DOUBLE QUOTATION MARK", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
10, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"fence",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\8221", description :: Text
description = Text
"RIGHT DOUBLE QUOTATION MARK", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
10, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"fence",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\8222", description :: Text
description = Text
"DOUBLE LOW-9 QUOTATION MARK", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\8223", description :: Text
description = Text
"DOUBLE HIGH-REVERSED-9 QUOTATION MARK", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\8226", description :: Text
description = Text
"BULLET", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
390, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8230", description :: Text
description = Text
"HORIZONTAL ELLIPSIS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
150, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8242", description :: Text
description = Text
"PRIME", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
800, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8243", description :: Text
description = Text
"DOUBLE PRIME", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8244", description :: Text
description = Text
"TRIPLE PRIME", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8245", description :: Text
description = Text
"REVERSED PRIME", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8246", description :: Text
description = Text
"REVERSED DOUBLE PRIME", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8247", description :: Text
description = Text
"REVERSED TRIPLE PRIME", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8254", description :: Text
description = Text
"OVERLINE", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8259", description :: Text
description = Text
"HYPHEN BULLET", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
390, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8260", description :: Text
description = Text
"FRACTION SLASH", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8279", description :: Text
description = Text
"QUADRUPLE PRIME", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8289", description :: Text
description = Text
"FUNCTION APPLICATION", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
850, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8290", description :: Text
description = Text
"INVISIBLE TIMES", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
390, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8291", description :: Text
description = Text
"INVISIBLE SEPARATOR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
40, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"separator"]}
  , Operator {oper :: Text
oper = Text
"\8292", description :: Text
description = Text
"INVISIBLE PLUS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8411", description :: Text
description = Text
"COMBINING THREE DOTS ABOVE", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8412", description :: Text
description = Text
"COMBINING FOUR DOTS ABOVE", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8517", description :: Text
description = Text
"DOUBLE-STRUCK ITALIC CAPITAL D", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
845, lspace :: Int
lspace = Int
2, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8518", description :: Text
description = Text
"DOUBLE-STRUCK ITALIC SMALL D", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
845, lspace :: Int
lspace = Int
2, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8592", description :: Text
description = Text
"LEFTWARDS ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8593", description :: Text
description = Text
"UPWARDS ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8594", description :: Text
description = Text
"RIGHTWARDS ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8595", description :: Text
description = Text
"DOWNWARDS ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8596", description :: Text
description = Text
"LEFT RIGHT ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8597", description :: Text
description = Text
"UP DOWN ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8598", description :: Text
description = Text
"NORTH WEST ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8599", description :: Text
description = Text
"NORTH EAST ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8600", description :: Text
description = Text
"SOUTH EAST ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8601", description :: Text
description = Text
"SOUTH WEST ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8602", description :: Text
description = Text
"LEFTWARDS ARROW WITH STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8603", description :: Text
description = Text
"RIGHTWARDS ARROW WITH STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8604", description :: Text
description = Text
"LEFTWARDS WAVE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8605", description :: Text
description = Text
"RIGHTWARDS WAVE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8606", description :: Text
description = Text
"LEFTWARDS TWO HEADED ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8607", description :: Text
description = Text
"UPWARDS TWO HEADED ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8608", description :: Text
description = Text
"RIGHTWARDS TWO HEADED ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8609", description :: Text
description = Text
"DOWNWARDS TWO HEADED ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8610", description :: Text
description = Text
"LEFTWARDS ARROW WITH TAIL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8611", description :: Text
description = Text
"RIGHTWARDS ARROW WITH TAIL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8612", description :: Text
description = Text
"LEFTWARDS ARROW FROM BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8613", description :: Text
description = Text
"UPWARDS ARROW FROM BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8614", description :: Text
description = Text
"RIGHTWARDS ARROW FROM BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8615", description :: Text
description = Text
"DOWNWARDS ARROW FROM BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8616", description :: Text
description = Text
"UP DOWN ARROW WITH BASE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8617", description :: Text
description = Text
"LEFTWARDS ARROW WITH HOOK", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8618", description :: Text
description = Text
"RIGHTWARDS ARROW WITH HOOK", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8619", description :: Text
description = Text
"LEFTWARDS ARROW WITH LOOP", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8620", description :: Text
description = Text
"RIGHTWARDS ARROW WITH LOOP", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8621", description :: Text
description = Text
"LEFT RIGHT WAVE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8622", description :: Text
description = Text
"LEFT RIGHT ARROW WITH STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8623", description :: Text
description = Text
"DOWNWARDS ZIGZAG ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8624", description :: Text
description = Text
"UPWARDS ARROW WITH TIP LEFTWARDS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8625", description :: Text
description = Text
"UPWARDS ARROW WITH TIP RIGHTWARDS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8626", description :: Text
description = Text
"DOWNWARDS ARROW WITH TIP LEFTWARDS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8627", description :: Text
description = Text
"DOWNWARDS ARROW WITH TIP RIGHTWARDS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8628", description :: Text
description = Text
"RIGHTWARDS ARROW WITH CORNER DOWNWARDS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8629", description :: Text
description = Text
"DOWNWARDS ARROW WITH CORNER LEFTWARDS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8630", description :: Text
description = Text
"ANTICLOCKWISE TOP SEMICIRCLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8631", description :: Text
description = Text
"CLOCKWISE TOP SEMICIRCLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8632", description :: Text
description = Text
"NORTH WEST ARROW TO LONG BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8633", description :: Text
description = Text
"LEFTWARDS ARROW TO BAR OVER RIGHTWARDS ARROW TO BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8634", description :: Text
description = Text
"ANTICLOCKWISE OPEN CIRCLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8635", description :: Text
description = Text
"CLOCKWISE OPEN CIRCLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8636", description :: Text
description = Text
"LEFTWARDS HARPOON WITH BARB UPWARDS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8637", description :: Text
description = Text
"LEFTWARDS HARPOON WITH BARB DOWNWARDS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8638", description :: Text
description = Text
"UPWARDS HARPOON WITH BARB RIGHTWARDS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8639", description :: Text
description = Text
"UPWARDS HARPOON WITH BARB LEFTWARDS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8640", description :: Text
description = Text
"RIGHTWARDS HARPOON WITH BARB UPWARDS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8641", description :: Text
description = Text
"RIGHTWARDS HARPOON WITH BARB DOWNWARDS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8642", description :: Text
description = Text
"DOWNWARDS HARPOON WITH BARB RIGHTWARDS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8643", description :: Text
description = Text
"DOWNWARDS HARPOON WITH BARB LEFTWARDS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8644", description :: Text
description = Text
"RIGHTWARDS ARROW OVER LEFTWARDS ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8645", description :: Text
description = Text
"UPWARDS ARROW LEFTWARDS OF DOWNWARDS ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8646", description :: Text
description = Text
"LEFTWARDS ARROW OVER RIGHTWARDS ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8647", description :: Text
description = Text
"LEFTWARDS PAIRED ARROWS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8648", description :: Text
description = Text
"UPWARDS PAIRED ARROWS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8649", description :: Text
description = Text
"RIGHTWARDS PAIRED ARROWS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8650", description :: Text
description = Text
"DOWNWARDS PAIRED ARROWS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8651", description :: Text
description = Text
"LEFTWARDS HARPOON OVER RIGHTWARDS HARPOON", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8652", description :: Text
description = Text
"RIGHTWARDS HARPOON OVER LEFTWARDS HARPOON", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8653", description :: Text
description = Text
"LEFTWARDS DOUBLE ARROW WITH STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8654", description :: Text
description = Text
"LEFT RIGHT DOUBLE ARROW WITH STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8655", description :: Text
description = Text
"RIGHTWARDS DOUBLE ARROW WITH STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8656", description :: Text
description = Text
"LEFTWARDS DOUBLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8657", description :: Text
description = Text
"UPWARDS DOUBLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8658", description :: Text
description = Text
"RIGHTWARDS DOUBLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8659", description :: Text
description = Text
"DOWNWARDS DOUBLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8660", description :: Text
description = Text
"LEFT RIGHT DOUBLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8661", description :: Text
description = Text
"UP DOWN DOUBLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8662", description :: Text
description = Text
"NORTH WEST DOUBLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8663", description :: Text
description = Text
"NORTH EAST DOUBLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8664", description :: Text
description = Text
"SOUTH EAST DOUBLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8665", description :: Text
description = Text
"SOUTH WEST DOUBLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8666", description :: Text
description = Text
"LEFTWARDS TRIPLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8667", description :: Text
description = Text
"RIGHTWARDS TRIPLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8668", description :: Text
description = Text
"LEFTWARDS SQUIGGLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8669", description :: Text
description = Text
"RIGHTWARDS SQUIGGLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8670", description :: Text
description = Text
"UPWARDS ARROW WITH DOUBLE STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8671", description :: Text
description = Text
"DOWNWARDS ARROW WITH DOUBLE STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8672", description :: Text
description = Text
"LEFTWARDS DASHED ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8673", description :: Text
description = Text
"UPWARDS DASHED ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8674", description :: Text
description = Text
"RIGHTWARDS DASHED ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8675", description :: Text
description = Text
"DOWNWARDS DASHED ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8676", description :: Text
description = Text
"LEFTWARDS ARROW TO BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8677", description :: Text
description = Text
"RIGHTWARDS ARROW TO BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8678", description :: Text
description = Text
"LEFTWARDS WHITE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8679", description :: Text
description = Text
"UPWARDS WHITE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8680", description :: Text
description = Text
"RIGHTWARDS WHITE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8681", description :: Text
description = Text
"DOWNWARDS WHITE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8682", description :: Text
description = Text
"UPWARDS WHITE ARROW FROM BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8683", description :: Text
description = Text
"UPWARDS WHITE ARROW ON PEDESTAL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8684", description :: Text
description = Text
"UPWARDS WHITE ARROW ON PEDESTAL WITH HORIZONTAL BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8685", description :: Text
description = Text
"UPWARDS WHITE ARROW ON PEDESTAL WITH VERTICAL BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8686", description :: Text
description = Text
"UPWARDS WHITE DOUBLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8687", description :: Text
description = Text
"UPWARDS WHITE DOUBLE ARROW ON PEDESTAL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8688", description :: Text
description = Text
"RIGHTWARDS WHITE ARROW FROM WALL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8689", description :: Text
description = Text
"NORTH WEST ARROW TO CORNER", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8690", description :: Text
description = Text
"SOUTH EAST ARROW TO CORNER", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8691", description :: Text
description = Text
"UP DOWN WHITE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8692", description :: Text
description = Text
"RIGHT ARROW WITH SMALL CIRCLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8693", description :: Text
description = Text
"DOWNWARDS ARROW LEFTWARDS OF UPWARDS ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\8694", description :: Text
description = Text
"THREE RIGHTWARDS ARROWS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8695", description :: Text
description = Text
"LEFTWARDS ARROW WITH VERTICAL STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8696", description :: Text
description = Text
"RIGHTWARDS ARROW WITH VERTICAL STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8697", description :: Text
description = Text
"LEFT RIGHT ARROW WITH VERTICAL STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8698", description :: Text
description = Text
"LEFTWARDS ARROW WITH DOUBLE VERTICAL STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8699", description :: Text
description = Text
"RIGHTWARDS ARROW WITH DOUBLE VERTICAL STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8700", description :: Text
description = Text
"LEFT RIGHT ARROW WITH DOUBLE VERTICAL STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8701", description :: Text
description = Text
"LEFTWARDS OPEN-HEADED ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8702", description :: Text
description = Text
"RIGHTWARDS OPEN-HEADED ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8703", description :: Text
description = Text
"LEFT RIGHT OPEN-HEADED ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\8704", description :: Text
description = Text
"FOR ALL", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
230, lspace :: Int
lspace = Int
2, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8705", description :: Text
description = Text
"COMPLEMENT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
240, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8706", description :: Text
description = Text
"PARTIAL DIFFERENTIAL", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
740, lspace :: Int
lspace = Int
2, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8707", description :: Text
description = Text
"THERE EXISTS", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
230, lspace :: Int
lspace = Int
2, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8708", description :: Text
description = Text
"THERE DOES NOT EXIST", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
230, lspace :: Int
lspace = Int
2, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8710", description :: Text
description = Text
"INCREMENT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8711", description :: Text
description = Text
"NABLA", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
740, lspace :: Int
lspace = Int
2, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8712", description :: Text
description = Text
"ELEMENT OF", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
240, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8713", description :: Text
description = Text
"NOT AN ELEMENT OF", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
240, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8714", description :: Text
description = Text
"SMALL ELEMENT OF", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8715", description :: Text
description = Text
"CONTAINS AS MEMBER", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
160, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8716", description :: Text
description = Text
"DOES NOT CONTAIN AS MEMBER", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
240, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8717", description :: Text
description = Text
"SMALL CONTAINS AS MEMBER", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8718", description :: Text
description = Text
"END OF PROOF", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8719", description :: Text
description = Text
"N-ARY PRODUCT", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
350, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"movablelimits"]}
  , Operator {oper :: Text
oper = Text
"\8720", description :: Text
description = Text
"N-ARY COPRODUCT", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
350, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"movablelimits"]}
  , Operator {oper :: Text
oper = Text
"\8721", description :: Text
description = Text
"N-ARY SUMMATION", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
290, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"movablelimits",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\8722", description :: Text
description = Text
"MINUS SIGN", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
275, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8722", description :: Text
description = Text
"MINUS SIGN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
275, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8723", description :: Text
description = Text
"MINUS-OR-PLUS SIGN", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
275, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8723", description :: Text
description = Text
"MINUS-OR-PLUS SIGN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
275, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8724", description :: Text
description = Text
"DOT PLUS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
275, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8725", description :: Text
description = Text
"DIVISION SLASH", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = [Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\8726", description :: Text
description = Text
"SET MINUS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
650, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8727", description :: Text
description = Text
"ASTERISK OPERATOR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8728", description :: Text
description = Text
"RING OPERATOR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8729", description :: Text
description = Text
"BULLET OPERATOR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8730", description :: Text
description = Text
"SQUARE ROOT", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
845, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = [Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\8731", description :: Text
description = Text
"CUBE ROOT", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
845, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8732", description :: Text
description = Text
"FOURTH ROOT", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
845, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8733", description :: Text
description = Text
"PROPORTIONAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8735", description :: Text
description = Text
"RIGHT ANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8736", description :: Text
description = Text
"ANGLE", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
670, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8737", description :: Text
description = Text
"MEASURED ANGLE", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
670, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8738", description :: Text
description = Text
"SPHERICAL ANGLE", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
670, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8739", description :: Text
description = Text
"DIVIDES", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8740", description :: Text
description = Text
"DOES NOT DIVIDE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8741", description :: Text
description = Text
"PARALLEL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8742", description :: Text
description = Text
"NOT PARALLEL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8743", description :: Text
description = Text
"LOGICAL AND", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
200, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8744", description :: Text
description = Text
"LOGICAL OR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
190, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8745", description :: Text
description = Text
"INTERSECTION", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
350, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8746", description :: Text
description = Text
"UNION", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
350, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8747", description :: Text
description = Text
"INTEGRAL", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
310, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\8748", description :: Text
description = Text
"DOUBLE INTEGRAL", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
300, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\8749", description :: Text
description = Text
"TRIPLE INTEGRAL", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
300, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\8750", description :: Text
description = Text
"CONTOUR INTEGRAL", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
310, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\8751", description :: Text
description = Text
"SURFACE INTEGRAL", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
310, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\8752", description :: Text
description = Text
"VOLUME INTEGRAL", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
310, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\8753", description :: Text
description = Text
"CLOCKWISE INTEGRAL", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
310, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\8754", description :: Text
description = Text
"CLOCKWISE CONTOUR INTEGRAL", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
310, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\8755", description :: Text
description = Text
"ANTICLOCKWISE CONTOUR INTEGRAL", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
310, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\8756", description :: Text
description = Text
"THEREFORE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
70, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8757", description :: Text
description = Text
"BECAUSE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
70, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8758", description :: Text
description = Text
"RATIO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8759", description :: Text
description = Text
"PROPORTION", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8760", description :: Text
description = Text
"DOT MINUS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8761", description :: Text
description = Text
"EXCESS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8762", description :: Text
description = Text
"GEOMETRIC PROPORTION", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8763", description :: Text
description = Text
"HOMOTHETIC", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8764", description :: Text
description = Text
"TILDE OPERATOR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
250, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8765", description :: Text
description = Text
"REVERSED TILDE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8765\817", description :: Text
description = Text
"REVERSED TILDE with underline", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8766", description :: Text
description = Text
"INVERTED LAZY S", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8767", description :: Text
description = Text
"SINE WAVE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8768", description :: Text
description = Text
"WREATH PRODUCT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
340, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8769", description :: Text
description = Text
"NOT TILDE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8770", description :: Text
description = Text
"MINUS TILDE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8770\824", description :: Text
description = Text
"MINUS TILDE with slash", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8771", description :: Text
description = Text
"ASYMPTOTICALLY EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8772", description :: Text
description = Text
"NOT ASYMPTOTICALLY EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8773", description :: Text
description = Text
"APPROXIMATELY EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8774", description :: Text
description = Text
"APPROXIMATELY BUT NOT ACTUALLY EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8775", description :: Text
description = Text
"NEITHER APPROXIMATELY NOR ACTUALLY EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8776", description :: Text
description = Text
"ALMOST EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
247, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8777", description :: Text
description = Text
"NOT ALMOST EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
250, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8778", description :: Text
description = Text
"ALMOST EQUAL OR EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8779", description :: Text
description = Text
"TRIPLE TILDE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8780", description :: Text
description = Text
"ALL EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8781", description :: Text
description = Text
"EQUIVALENT TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8782", description :: Text
description = Text
"GEOMETRICALLY EQUIVALENT TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8782\824", description :: Text
description = Text
"GEOMETRICALLY EQUIVALENT TO with slash", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8783", description :: Text
description = Text
"DIFFERENCE BETWEEN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8783\824", description :: Text
description = Text
"DIFFERENCE BETWEEN with slash", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8784", description :: Text
description = Text
"APPROACHES THE LIMIT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8785", description :: Text
description = Text
"GEOMETRICALLY EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8786", description :: Text
description = Text
"APPROXIMATELY EQUAL TO OR THE IMAGE OF", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8787", description :: Text
description = Text
"IMAGE OF OR APPROXIMATELY EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8788", description :: Text
description = Text
"COLON EQUALS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8789", description :: Text
description = Text
"EQUALS COLON", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8790", description :: Text
description = Text
"RING IN EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8791", description :: Text
description = Text
"RING EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8792", description :: Text
description = Text
"CORRESPONDS TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8793", description :: Text
description = Text
"ESTIMATES", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8794", description :: Text
description = Text
"EQUIANGULAR TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8795", description :: Text
description = Text
"STAR EQUALS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8796", description :: Text
description = Text
"DELTA EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8797", description :: Text
description = Text
"EQUAL TO BY DEFINITION", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8798", description :: Text
description = Text
"MEASURED BY", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8799", description :: Text
description = Text
"QUESTIONED EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8800", description :: Text
description = Text
"NOT EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
255, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8801", description :: Text
description = Text
"IDENTICAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8802", description :: Text
description = Text
"NOT IDENTICAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
252, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8803", description :: Text
description = Text
"STRICTLY EQUIVALENT TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8804", description :: Text
description = Text
"LESS-THAN OR EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
241, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8805", description :: Text
description = Text
"GREATER-THAN OR EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
242, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8806", description :: Text
description = Text
"LESS-THAN OVER EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8806\824", description :: Text
description = Text
"LESS-THAN OVER EQUAL TO with slash", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8807", description :: Text
description = Text
"GREATER-THAN OVER EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8808", description :: Text
description = Text
"LESS-THAN BUT NOT EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8809", description :: Text
description = Text
"GREATER-THAN BUT NOT EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8810", description :: Text
description = Text
"MUCH LESS-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8810\824", description :: Text
description = Text
"MUCH LESS THAN with slash", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8811", description :: Text
description = Text
"MUCH GREATER-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8811\824", description :: Text
description = Text
"MUCH GREATER THAN with slash", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8812", description :: Text
description = Text
"BETWEEN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8813", description :: Text
description = Text
"NOT EQUIVALENT TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8814", description :: Text
description = Text
"NOT LESS-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
246, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8815", description :: Text
description = Text
"NOT GREATER-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
244, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8816", description :: Text
description = Text
"NEITHER LESS-THAN NOR EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8817", description :: Text
description = Text
"NEITHER GREATER-THAN NOR EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8818", description :: Text
description = Text
"LESS-THAN OR EQUIVALENT TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8819", description :: Text
description = Text
"GREATER-THAN OR EQUIVALENT TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8820", description :: Text
description = Text
"NEITHER LESS-THAN NOR EQUIVALENT TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8821", description :: Text
description = Text
"NEITHER GREATER-THAN NOR EQUIVALENT TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8822", description :: Text
description = Text
"LESS-THAN OR GREATER-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8823", description :: Text
description = Text
"GREATER-THAN OR LESS-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8824", description :: Text
description = Text
"NEITHER LESS-THAN NOR GREATER-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8825", description :: Text
description = Text
"NEITHER GREATER-THAN NOR LESS-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8826", description :: Text
description = Text
"PRECEDES", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8827", description :: Text
description = Text
"SUCCEEDS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8828", description :: Text
description = Text
"PRECEDES OR EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8829", description :: Text
description = Text
"SUCCEEDS OR EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8830", description :: Text
description = Text
"PRECEDES OR EQUIVALENT TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8831", description :: Text
description = Text
"SUCCEEDS OR EQUIVALENT TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8831\824", description :: Text
description = Text
"SUCCEEDS OR EQUIVALENT TO with slash", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8832", description :: Text
description = Text
"DOES NOT PRECEDE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8833", description :: Text
description = Text
"DOES NOT SUCCEED", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8834", description :: Text
description = Text
"SUBSET OF", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
240, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8834\8402", description :: Text
description = Text
"SUBSET OF with vertical line", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
240, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8835", description :: Text
description = Text
"SUPERSET OF", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
240, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8835\8402", description :: Text
description = Text
"SUPERSET OF with vertical line", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
240, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8836", description :: Text
description = Text
"NOT A SUBSET OF", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
240, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8837", description :: Text
description = Text
"NOT A SUPERSET OF", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
240, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8838", description :: Text
description = Text
"SUBSET OF OR EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
240, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8839", description :: Text
description = Text
"SUPERSET OF OR EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
240, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8840", description :: Text
description = Text
"NEITHER A SUBSET OF NOR EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
240, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8841", description :: Text
description = Text
"NEITHER A SUPERSET OF NOR EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
240, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8842", description :: Text
description = Text
"SUBSET OF WITH NOT EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
240, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8843", description :: Text
description = Text
"SUPERSET OF WITH NOT EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
240, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8844", description :: Text
description = Text
"MULTISET", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8845", description :: Text
description = Text
"MULTISET MULTIPLICATION", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8846", description :: Text
description = Text
"MULTISET UNION", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8847", description :: Text
description = Text
"SQUARE IMAGE OF", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8847\824", description :: Text
description = Text
"SQUARE IMAGE OF with slash", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8848", description :: Text
description = Text
"SQUARE ORIGINAL OF", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8848\824", description :: Text
description = Text
"SQUARE ORIGINAL OF with slash", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8849", description :: Text
description = Text
"SQUARE IMAGE OF OR EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8850", description :: Text
description = Text
"SQUARE ORIGINAL OF OR EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8851", description :: Text
description = Text
"SQUARE CAP", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8852", description :: Text
description = Text
"SQUARE CUP", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8853", description :: Text
description = Text
"CIRCLED PLUS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
300, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8854", description :: Text
description = Text
"CIRCLED MINUS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
300, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8855", description :: Text
description = Text
"CIRCLED TIMES", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
410, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8856", description :: Text
description = Text
"CIRCLED DIVISION SLASH", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
300, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8857", description :: Text
description = Text
"CIRCLED DOT OPERATOR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
710, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8858", description :: Text
description = Text
"CIRCLED RING OPERATOR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8859", description :: Text
description = Text
"CIRCLED ASTERISK OPERATOR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8860", description :: Text
description = Text
"CIRCLED EQUALS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8861", description :: Text
description = Text
"CIRCLED DASH", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8862", description :: Text
description = Text
"SQUARED PLUS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
275, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8863", description :: Text
description = Text
"SQUARED MINUS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
275, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8864", description :: Text
description = Text
"SQUARED TIMES", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
390, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8865", description :: Text
description = Text
"SQUARED DOT OPERATOR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
390, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8866", description :: Text
description = Text
"RIGHT TACK", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
170, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8867", description :: Text
description = Text
"LEFT TACK", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
170, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8868", description :: Text
description = Text
"DOWN TACK", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
170, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8869", description :: Text
description = Text
"UP TACK", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8870", description :: Text
description = Text
"ASSERTION", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8871", description :: Text
description = Text
"MODELS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8872", description :: Text
description = Text
"TRUE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
170, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8873", description :: Text
description = Text
"FORCES", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
170, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8874", description :: Text
description = Text
"TRIPLE VERTICAL BAR RIGHT TURNSTILE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8875", description :: Text
description = Text
"DOUBLE VERTICAL BAR DOUBLE RIGHT TURNSTILE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8876", description :: Text
description = Text
"DOES NOT PROVE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
170, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8877", description :: Text
description = Text
"NOT TRUE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
170, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8878", description :: Text
description = Text
"DOES NOT FORCE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
170, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8879", description :: Text
description = Text
"NEGATED DOUBLE VERTICAL BAR DOUBLE RIGHT TURNSTILE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
170, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8880", description :: Text
description = Text
"PRECEDES UNDER RELATION", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8881", description :: Text
description = Text
"SUCCEEDS UNDER RELATION", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8882", description :: Text
description = Text
"NORMAL SUBGROUP OF", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8883", description :: Text
description = Text
"CONTAINS AS NORMAL SUBGROUP", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8884", description :: Text
description = Text
"NORMAL SUBGROUP OF OR EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8885", description :: Text
description = Text
"CONTAINS AS NORMAL SUBGROUP OR EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8886", description :: Text
description = Text
"ORIGINAL OF", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8887", description :: Text
description = Text
"IMAGE OF", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8888", description :: Text
description = Text
"MULTIMAP", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8889", description :: Text
description = Text
"HERMITIAN CONJUGATE MATRIX", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8890", description :: Text
description = Text
"INTERCALATE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8891", description :: Text
description = Text
"XOR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8892", description :: Text
description = Text
"NAND", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8893", description :: Text
description = Text
"NOR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8894", description :: Text
description = Text
"RIGHT ANGLE WITH ARC", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8895", description :: Text
description = Text
"RIGHT TRIANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8896", description :: Text
description = Text
"N-ARY LOGICAL AND", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
330, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"movablelimits"]}
  , Operator {oper :: Text
oper = Text
"\8897", description :: Text
description = Text
"N-ARY LOGICAL OR", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
330, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"movablelimits"]}
  , Operator {oper :: Text
oper = Text
"\8898", description :: Text
description = Text
"N-ARY INTERSECTION", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
330, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"movablelimits"]}
  , Operator {oper :: Text
oper = Text
"\8899", description :: Text
description = Text
"N-ARY UNION", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
320, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"movablelimits"]}
  , Operator {oper :: Text
oper = Text
"\8900", description :: Text
description = Text
"DIAMOND OPERATOR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8901", description :: Text
description = Text
"DOT OPERATOR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
390, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8902", description :: Text
description = Text
"STAR OPERATOR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8903", description :: Text
description = Text
"DIVISION TIMES", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8904", description :: Text
description = Text
"BOWTIE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8905", description :: Text
description = Text
"LEFT NORMAL FACTOR SEMIDIRECT PRODUCT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8906", description :: Text
description = Text
"RIGHT NORMAL FACTOR SEMIDIRECT PRODUCT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8907", description :: Text
description = Text
"LEFT SEMIDIRECT PRODUCT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8908", description :: Text
description = Text
"RIGHT SEMIDIRECT PRODUCT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8909", description :: Text
description = Text
"REVERSED TILDE EQUALS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8910", description :: Text
description = Text
"CURLY LOGICAL OR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8911", description :: Text
description = Text
"CURLY LOGICAL AND", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8912", description :: Text
description = Text
"DOUBLE SUBSET", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8913", description :: Text
description = Text
"DOUBLE SUPERSET", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8914", description :: Text
description = Text
"DOUBLE INTERSECTION", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8915", description :: Text
description = Text
"DOUBLE UNION", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8916", description :: Text
description = Text
"PITCHFORK", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8917", description :: Text
description = Text
"EQUAL AND PARALLEL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8918", description :: Text
description = Text
"LESS-THAN WITH DOT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8919", description :: Text
description = Text
"GREATER-THAN WITH DOT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8920", description :: Text
description = Text
"VERY MUCH LESS-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8921", description :: Text
description = Text
"VERY MUCH GREATER-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8922", description :: Text
description = Text
"LESS-THAN EQUAL TO OR GREATER-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8923", description :: Text
description = Text
"GREATER-THAN EQUAL TO OR LESS-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8924", description :: Text
description = Text
"EQUAL TO OR LESS-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8925", description :: Text
description = Text
"EQUAL TO OR GREATER-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8926", description :: Text
description = Text
"EQUAL TO OR PRECEDES", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8927", description :: Text
description = Text
"EQUAL TO OR SUCCEEDS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8928", description :: Text
description = Text
"DOES NOT PRECEDE OR EQUAL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8929", description :: Text
description = Text
"DOES NOT SUCCEED OR EQUAL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8930", description :: Text
description = Text
"NOT SQUARE IMAGE OF OR EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8931", description :: Text
description = Text
"NOT SQUARE ORIGINAL OF OR EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8932", description :: Text
description = Text
"SQUARE IMAGE OF OR NOT EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8933", description :: Text
description = Text
"SQUARE ORIGINAL OF OR NOT EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8934", description :: Text
description = Text
"LESS-THAN BUT NOT EQUIVALENT TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8935", description :: Text
description = Text
"GREATER-THAN BUT NOT EQUIVALENT TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8936", description :: Text
description = Text
"PRECEDES BUT NOT EQUIVALENT TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8937", description :: Text
description = Text
"SUCCEEDS BUT NOT EQUIVALENT TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8938", description :: Text
description = Text
"NOT NORMAL SUBGROUP OF", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8939", description :: Text
description = Text
"DOES NOT CONTAIN AS NORMAL SUBGROUP", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8940", description :: Text
description = Text
"NOT NORMAL SUBGROUP OF OR EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8941", description :: Text
description = Text
"DOES NOT CONTAIN AS NORMAL SUBGROUP OR EQUAL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8942", description :: Text
description = Text
"VERTICAL ELLIPSIS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
150, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8943", description :: Text
description = Text
"MIDLINE HORIZONTAL ELLIPSIS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
150, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8944", description :: Text
description = Text
"UP RIGHT DIAGONAL ELLIPSIS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8945", description :: Text
description = Text
"DOWN RIGHT DIAGONAL ELLIPSIS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
150, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8946", description :: Text
description = Text
"ELEMENT OF WITH LONG HORIZONTAL STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8947", description :: Text
description = Text
"ELEMENT OF WITH VERTICAL BAR AT END OF HORIZONTAL STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8948", description :: Text
description = Text
"SMALL ELEMENT OF WITH VERTICAL BAR AT END OF HORIZONTAL STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8949", description :: Text
description = Text
"ELEMENT OF WITH DOT ABOVE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8950", description :: Text
description = Text
"ELEMENT OF WITH OVERBAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8951", description :: Text
description = Text
"SMALL ELEMENT OF WITH OVERBAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8952", description :: Text
description = Text
"ELEMENT OF WITH UNDERBAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8953", description :: Text
description = Text
"ELEMENT OF WITH TWO HORIZONTAL STROKES", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8954", description :: Text
description = Text
"CONTAINS WITH LONG HORIZONTAL STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8955", description :: Text
description = Text
"CONTAINS WITH VERTICAL BAR AT END OF HORIZONTAL STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8956", description :: Text
description = Text
"SMALL CONTAINS WITH VERTICAL BAR AT END OF HORIZONTAL STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8957", description :: Text
description = Text
"CONTAINS WITH OVERBAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8958", description :: Text
description = Text
"SMALL CONTAINS WITH OVERBAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8959", description :: Text
description = Text
"Z NOTATION BAG MEMBERSHIP", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\8968", description :: Text
description = Text
"LEFT CEILING", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\8969", description :: Text
description = Text
"RIGHT CEILING", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\8970", description :: Text
description = Text
"LEFT FLOOR", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\8971", description :: Text
description = Text
"RIGHT FLOOR", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\9001", description :: Text
description = Text
"LEFT-POINTING ANGLE BRACKET", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\9002", description :: Text
description = Text
"RIGHT-POINTING ANGLE BRACKET", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\9140", description :: Text
description = Text
"TOP SQUARE BRACKET", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\9141", description :: Text
description = Text
"BOTTOM SQUARE BRACKET", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\9180", description :: Text
description = Text
"TOP PARENTHESIS", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\9181", description :: Text
description = Text
"BOTTOM PARENTHESIS", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\9182", description :: Text
description = Text
"TOP CURLY BRACKET", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\9183", description :: Text
description = Text
"BOTTOM CURLY BRACKET", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\9184", description :: Text
description = Text
"TOP TORTOISE SHELL BRACKET", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\9185", description :: Text
description = Text
"BOTTOM TORTOISE SHELL BRACKET", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"accent",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\9632", description :: Text
description = Text
"BLACK SQUARE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9633", description :: Text
description = Text
"WHITE SQUARE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9642", description :: Text
description = Text
"BLACK SMALL SQUARE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9643", description :: Text
description = Text
"WHITE SMALL SQUARE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9645", description :: Text
description = Text
"WHITE RECTANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9646", description :: Text
description = Text
"BLACK VERTICAL RECTANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9647", description :: Text
description = Text
"WHITE VERTICAL RECTANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9648", description :: Text
description = Text
"BLACK PARALLELOGRAM", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9649", description :: Text
description = Text
"WHITE PARALLELOGRAM", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9650", description :: Text
description = Text
"BLACK UP-POINTING TRIANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9651", description :: Text
description = Text
"WHITE UP-POINTING TRIANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9652", description :: Text
description = Text
"BLACK UP-POINTING SMALL TRIANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9653", description :: Text
description = Text
"WHITE UP-POINTING SMALL TRIANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9654", description :: Text
description = Text
"BLACK RIGHT-POINTING TRIANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9655", description :: Text
description = Text
"WHITE RIGHT-POINTING TRIANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9656", description :: Text
description = Text
"BLACK RIGHT-POINTING SMALL TRIANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9657", description :: Text
description = Text
"WHITE RIGHT-POINTING SMALL TRIANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9660", description :: Text
description = Text
"BLACK DOWN-POINTING TRIANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9661", description :: Text
description = Text
"WHITE DOWN-POINTING TRIANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9662", description :: Text
description = Text
"BLACK DOWN-POINTING SMALL TRIANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9663", description :: Text
description = Text
"WHITE DOWN-POINTING SMALL TRIANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9664", description :: Text
description = Text
"BLACK LEFT-POINTING TRIANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9665", description :: Text
description = Text
"WHITE LEFT-POINTING TRIANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9666", description :: Text
description = Text
"BLACK LEFT-POINTING SMALL TRIANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9667", description :: Text
description = Text
"WHITE LEFT-POINTING SMALL TRIANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9668", description :: Text
description = Text
"BLACK LEFT-POINTING POINTER", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9669", description :: Text
description = Text
"WHITE LEFT-POINTING POINTER", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9670", description :: Text
description = Text
"BLACK DIAMOND", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9671", description :: Text
description = Text
"WHITE DIAMOND", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9672", description :: Text
description = Text
"WHITE DIAMOND CONTAINING BLACK SMALL DIAMOND", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9673", description :: Text
description = Text
"FISHEYE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9676", description :: Text
description = Text
"DOTTED CIRCLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9677", description :: Text
description = Text
"CIRCLE WITH VERTICAL FILL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9678", description :: Text
description = Text
"BULLSEYE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9679", description :: Text
description = Text
"BLACK CIRCLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9686", description :: Text
description = Text
"LEFT HALF BLACK CIRCLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9687", description :: Text
description = Text
"RIGHT HALF BLACK CIRCLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9702", description :: Text
description = Text
"WHITE BULLET", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9837", description :: Text
description = Text
"MUSIC FLAT SIGN", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
800, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9838", description :: Text
description = Text
"MUSIC NATURAL SIGN", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
800, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\9839", description :: Text
description = Text
"MUSIC SHARP SIGN", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
800, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10072", description :: Text
description = Text
"LIGHT VERTICAL BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10098", description :: Text
description = Text
"LIGHT LEFT TORTOISE SHELL BRACKET ORNAMENT", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10099", description :: Text
description = Text
"LIGHT RIGHT TORTOISE SHELL BRACKET ORNAMENT", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10214", description :: Text
description = Text
"MATHEMATICAL LEFT WHITE SQUARE BRACKET", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10215", description :: Text
description = Text
"MATHEMATICAL RIGHT WHITE SQUARE BRACKET", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10216", description :: Text
description = Text
"MATHEMATICAL LEFT ANGLE BRACKET", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10217", description :: Text
description = Text
"MATHEMATICAL RIGHT ANGLE BRACKET", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10218", description :: Text
description = Text
"MATHEMATICAL LEFT DOUBLE ANGLE BRACKET", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10219", description :: Text
description = Text
"MATHEMATICAL RIGHT DOUBLE ANGLE BRACKET", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10220", description :: Text
description = Text
"MATHEMATICAL LEFT WHITE TORTOISE SHELL BRACKET", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10221", description :: Text
description = Text
"MATHEMATICAL RIGHT WHITE TORTOISE SHELL BRACKET", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10222", description :: Text
description = Text
"MATHEMATICAL LEFT FLATTENED PARENTHESIS", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10223", description :: Text
description = Text
"MATHEMATICAL RIGHT FLATTENED PARENTHESIS", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10224", description :: Text
description = Text
"UPWARDS QUADRUPLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\10225", description :: Text
description = Text
"DOWNWARDS QUADRUPLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\10229", description :: Text
description = Text
"LONG LEFTWARDS ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10230", description :: Text
description = Text
"LONG RIGHTWARDS ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10231", description :: Text
description = Text
"LONG LEFT RIGHT ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10232", description :: Text
description = Text
"LONG LEFTWARDS DOUBLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10233", description :: Text
description = Text
"LONG RIGHTWARDS DOUBLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10234", description :: Text
description = Text
"LONG LEFT RIGHT DOUBLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10235", description :: Text
description = Text
"LONG LEFTWARDS ARROW FROM BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10236", description :: Text
description = Text
"LONG RIGHTWARDS ARROW FROM BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10237", description :: Text
description = Text
"LONG LEFTWARDS DOUBLE ARROW FROM BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10238", description :: Text
description = Text
"LONG RIGHTWARDS DOUBLE ARROW FROM BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10239", description :: Text
description = Text
"LONG RIGHTWARDS SQUIGGLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10496", description :: Text
description = Text
"RIGHTWARDS TWO-HEADED ARROW WITH VERTICAL STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10497", description :: Text
description = Text
"RIGHTWARDS TWO-HEADED ARROW WITH DOUBLE VERTICAL STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10498", description :: Text
description = Text
"LEFTWARDS DOUBLE ARROW WITH VERTICAL STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10499", description :: Text
description = Text
"RIGHTWARDS DOUBLE ARROW WITH VERTICAL STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10500", description :: Text
description = Text
"LEFT RIGHT DOUBLE ARROW WITH VERTICAL STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10501", description :: Text
description = Text
"RIGHTWARDS TWO-HEADED ARROW FROM BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10502", description :: Text
description = Text
"LEFTWARDS DOUBLE ARROW FROM BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10503", description :: Text
description = Text
"RIGHTWARDS DOUBLE ARROW FROM BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10504", description :: Text
description = Text
"DOWNWARDS ARROW WITH HORIZONTAL STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10505", description :: Text
description = Text
"UPWARDS ARROW WITH HORIZONTAL STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10506", description :: Text
description = Text
"UPWARDS TRIPLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\10507", description :: Text
description = Text
"DOWNWARDS TRIPLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\10508", description :: Text
description = Text
"LEFTWARDS DOUBLE DASH ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10509", description :: Text
description = Text
"RIGHTWARDS DOUBLE DASH ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10510", description :: Text
description = Text
"LEFTWARDS TRIPLE DASH ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10511", description :: Text
description = Text
"RIGHTWARDS TRIPLE DASH ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10512", description :: Text
description = Text
"RIGHTWARDS TWO-HEADED TRIPLE DASH ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10513", description :: Text
description = Text
"RIGHTWARDS ARROW WITH DOTTED STEM", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10514", description :: Text
description = Text
"UPWARDS ARROW TO BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\10515", description :: Text
description = Text
"DOWNWARDS ARROW TO BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\10516", description :: Text
description = Text
"RIGHTWARDS ARROW WITH TAIL WITH VERTICAL STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10517", description :: Text
description = Text
"RIGHTWARDS ARROW WITH TAIL WITH DOUBLE VERTICAL STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10518", description :: Text
description = Text
"RIGHTWARDS TWO-HEADED ARROW WITH TAIL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10519", description :: Text
description = Text
"RIGHTWARDS TWO-HEADED ARROW WITH TAIL WITH VERTICAL STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10520", description :: Text
description = Text
"RIGHTWARDS TWO-HEADED ARROW WITH TAIL WITH DOUBLE VERTICAL STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10521", description :: Text
description = Text
"LEFTWARDS ARROW-TAIL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10522", description :: Text
description = Text
"RIGHTWARDS ARROW-TAIL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10523", description :: Text
description = Text
"LEFTWARDS DOUBLE ARROW-TAIL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10524", description :: Text
description = Text
"RIGHTWARDS DOUBLE ARROW-TAIL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10525", description :: Text
description = Text
"LEFTWARDS ARROW TO BLACK DIAMOND", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10526", description :: Text
description = Text
"RIGHTWARDS ARROW TO BLACK DIAMOND", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10527", description :: Text
description = Text
"LEFTWARDS ARROW FROM BAR TO BLACK DIAMOND", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10528", description :: Text
description = Text
"RIGHTWARDS ARROW FROM BAR TO BLACK DIAMOND", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10529", description :: Text
description = Text
"NORTH WEST AND SOUTH EAST ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\10530", description :: Text
description = Text
"NORTH EAST AND SOUTH WEST ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\10531", description :: Text
description = Text
"NORTH WEST ARROW WITH HOOK", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10532", description :: Text
description = Text
"NORTH EAST ARROW WITH HOOK", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10533", description :: Text
description = Text
"SOUTH EAST ARROW WITH HOOK", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10534", description :: Text
description = Text
"SOUTH WEST ARROW WITH HOOK", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10535", description :: Text
description = Text
"NORTH WEST ARROW AND NORTH EAST ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10536", description :: Text
description = Text
"NORTH EAST ARROW AND SOUTH EAST ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10537", description :: Text
description = Text
"SOUTH EAST ARROW AND SOUTH WEST ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10538", description :: Text
description = Text
"SOUTH WEST ARROW AND NORTH WEST ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10539", description :: Text
description = Text
"RISING DIAGONAL CROSSING FALLING DIAGONAL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10540", description :: Text
description = Text
"FALLING DIAGONAL CROSSING RISING DIAGONAL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10541", description :: Text
description = Text
"SOUTH EAST ARROW CROSSING NORTH EAST ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10542", description :: Text
description = Text
"NORTH EAST ARROW CROSSING SOUTH EAST ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10543", description :: Text
description = Text
"FALLING DIAGONAL CROSSING NORTH EAST ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10544", description :: Text
description = Text
"RISING DIAGONAL CROSSING SOUTH EAST ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10545", description :: Text
description = Text
"NORTH EAST ARROW CROSSING NORTH WEST ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10546", description :: Text
description = Text
"NORTH WEST ARROW CROSSING NORTH EAST ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10547", description :: Text
description = Text
"WAVE ARROW POINTING DIRECTLY RIGHT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10548", description :: Text
description = Text
"ARROW POINTING RIGHTWARDS THEN CURVING UPWARDS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10549", description :: Text
description = Text
"ARROW POINTING RIGHTWARDS THEN CURVING DOWNWARDS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10550", description :: Text
description = Text
"ARROW POINTING DOWNWARDS THEN CURVING LEFTWARDS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10551", description :: Text
description = Text
"ARROW POINTING DOWNWARDS THEN CURVING RIGHTWARDS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10552", description :: Text
description = Text
"RIGHT-SIDE ARC CLOCKWISE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10553", description :: Text
description = Text
"LEFT-SIDE ARC ANTICLOCKWISE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10554", description :: Text
description = Text
"TOP ARC ANTICLOCKWISE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10555", description :: Text
description = Text
"BOTTOM ARC ANTICLOCKWISE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10556", description :: Text
description = Text
"TOP ARC CLOCKWISE ARROW WITH MINUS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10557", description :: Text
description = Text
"TOP ARC ANTICLOCKWISE ARROW WITH PLUS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10558", description :: Text
description = Text
"LOWER RIGHT SEMICIRCULAR CLOCKWISE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10559", description :: Text
description = Text
"LOWER LEFT SEMICIRCULAR ANTICLOCKWISE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10560", description :: Text
description = Text
"ANTICLOCKWISE CLOSED CIRCLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10561", description :: Text
description = Text
"CLOCKWISE CLOSED CIRCLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10562", description :: Text
description = Text
"RIGHTWARDS ARROW ABOVE SHORT LEFTWARDS ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10563", description :: Text
description = Text
"LEFTWARDS ARROW ABOVE SHORT RIGHTWARDS ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10564", description :: Text
description = Text
"SHORT RIGHTWARDS ARROW ABOVE LEFTWARDS ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10565", description :: Text
description = Text
"RIGHTWARDS ARROW WITH PLUS BELOW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10566", description :: Text
description = Text
"LEFTWARDS ARROW WITH PLUS BELOW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10567", description :: Text
description = Text
"RIGHTWARDS ARROW THROUGH X", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10568", description :: Text
description = Text
"LEFT RIGHT ARROW THROUGH SMALL CIRCLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10569", description :: Text
description = Text
"UPWARDS TWO-HEADED ARROW FROM SMALL CIRCLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10570", description :: Text
description = Text
"LEFT BARB UP RIGHT BARB DOWN HARPOON", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10571", description :: Text
description = Text
"LEFT BARB DOWN RIGHT BARB UP HARPOON", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10572", description :: Text
description = Text
"UP BARB RIGHT DOWN BARB LEFT HARPOON", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10573", description :: Text
description = Text
"UP BARB LEFT DOWN BARB RIGHT HARPOON", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10574", description :: Text
description = Text
"LEFT BARB UP RIGHT BARB UP HARPOON", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10575", description :: Text
description = Text
"UP BARB RIGHT DOWN BARB RIGHT HARPOON", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\10576", description :: Text
description = Text
"LEFT BARB DOWN RIGHT BARB DOWN HARPOON", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10577", description :: Text
description = Text
"UP BARB LEFT DOWN BARB LEFT HARPOON", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\10578", description :: Text
description = Text
"LEFTWARDS HARPOON WITH BARB UP TO BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10579", description :: Text
description = Text
"RIGHTWARDS HARPOON WITH BARB UP TO BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10580", description :: Text
description = Text
"UPWARDS HARPOON WITH BARB RIGHT TO BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\10581", description :: Text
description = Text
"DOWNWARDS HARPOON WITH BARB RIGHT TO BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\10582", description :: Text
description = Text
"LEFTWARDS HARPOON WITH BARB DOWN TO BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\10583", description :: Text
description = Text
"RIGHTWARDS HARPOON WITH BARB DOWN TO BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\10584", description :: Text
description = Text
"UPWARDS HARPOON WITH BARB LEFT TO BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\10585", description :: Text
description = Text
"DOWNWARDS HARPOON WITH BARB LEFT TO BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\10586", description :: Text
description = Text
"LEFTWARDS HARPOON WITH BARB UP FROM BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10587", description :: Text
description = Text
"RIGHTWARDS HARPOON WITH BARB UP FROM BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10588", description :: Text
description = Text
"UPWARDS HARPOON WITH BARB RIGHT FROM BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\10589", description :: Text
description = Text
"DOWNWARDS HARPOON WITH BARB RIGHT FROM BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\10590", description :: Text
description = Text
"LEFTWARDS HARPOON WITH BARB DOWN FROM BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10591", description :: Text
description = Text
"RIGHTWARDS HARPOON WITH BARB DOWN FROM BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10592", description :: Text
description = Text
"UPWARDS HARPOON WITH BARB LEFT FROM BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\10593", description :: Text
description = Text
"DOWNWARDS HARPOON WITH BARB LEFT FROM BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\10594", description :: Text
description = Text
"LEFTWARDS HARPOON WITH BARB UP ABOVE LEFTWARDS HARPOON WITH BARB DOWN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10595", description :: Text
description = Text
"UPWARDS HARPOON WITH BARB LEFT BESIDE UPWARDS HARPOON WITH BARB RIGHT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10596", description :: Text
description = Text
"RIGHTWARDS HARPOON WITH BARB UP ABOVE RIGHTWARDS HARPOON WITH BARB DOWN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10597", description :: Text
description = Text
"DOWNWARDS HARPOON WITH BARB LEFT BESIDE DOWNWARDS HARPOON WITH BARB RIGHT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10598", description :: Text
description = Text
"LEFTWARDS HARPOON WITH BARB UP ABOVE RIGHTWARDS HARPOON WITH BARB UP", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10599", description :: Text
description = Text
"LEFTWARDS HARPOON WITH BARB DOWN ABOVE RIGHTWARDS HARPOON WITH BARB DOWN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10600", description :: Text
description = Text
"RIGHTWARDS HARPOON WITH BARB UP ABOVE LEFTWARDS HARPOON WITH BARB UP", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10601", description :: Text
description = Text
"RIGHTWARDS HARPOON WITH BARB DOWN ABOVE LEFTWARDS HARPOON WITH BARB DOWN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10602", description :: Text
description = Text
"LEFTWARDS HARPOON WITH BARB UP ABOVE LONG DASH", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10603", description :: Text
description = Text
"LEFTWARDS HARPOON WITH BARB DOWN BELOW LONG DASH", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10604", description :: Text
description = Text
"RIGHTWARDS HARPOON WITH BARB UP ABOVE LONG DASH", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10605", description :: Text
description = Text
"RIGHTWARDS HARPOON WITH BARB DOWN BELOW LONG DASH", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10606", description :: Text
description = Text
"UPWARDS HARPOON WITH BARB LEFT BESIDE DOWNWARDS HARPOON WITH BARB RIGHT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\10607", description :: Text
description = Text
"DOWNWARDS HARPOON WITH BARB LEFT BESIDE UPWARDS HARPOON WITH BARB RIGHT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\10608", description :: Text
description = Text
"RIGHT DOUBLE ARROW WITH ROUNDED HEAD", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10609", description :: Text
description = Text
"EQUALS SIGN ABOVE RIGHTWARDS ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10610", description :: Text
description = Text
"TILDE OPERATOR ABOVE RIGHTWARDS ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10611", description :: Text
description = Text
"LEFTWARDS ARROW ABOVE TILDE OPERATOR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10612", description :: Text
description = Text
"RIGHTWARDS ARROW ABOVE TILDE OPERATOR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10613", description :: Text
description = Text
"RIGHTWARDS ARROW ABOVE ALMOST EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10614", description :: Text
description = Text
"LESS-THAN ABOVE LEFTWARDS ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10615", description :: Text
description = Text
"LEFTWARDS ARROW THROUGH LESS-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10616", description :: Text
description = Text
"GREATER-THAN ABOVE RIGHTWARDS ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10617", description :: Text
description = Text
"SUBSET ABOVE RIGHTWARDS ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10618", description :: Text
description = Text
"LEFTWARDS ARROW THROUGH SUBSET", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10619", description :: Text
description = Text
"SUPERSET ABOVE LEFTWARDS ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10620", description :: Text
description = Text
"LEFT FISH TAIL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10621", description :: Text
description = Text
"RIGHT FISH TAIL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\10622", description :: Text
description = Text
"UP FISH TAIL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10623", description :: Text
description = Text
"DOWN FISH TAIL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10624", description :: Text
description = Text
"TRIPLE VERTICAL BAR DELIMITER", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"fence",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\10624", description :: Text
description = Text
"TRIPLE VERTICAL BAR DELIMITER", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"fence",Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\10625", description :: Text
description = Text
"Z NOTATION SPOT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10626", description :: Text
description = Text
"Z NOTATION TYPE COLON", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10627", description :: Text
description = Text
"LEFT WHITE CURLY BRACKET", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10628", description :: Text
description = Text
"RIGHT WHITE CURLY BRACKET", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10629", description :: Text
description = Text
"LEFT WHITE PARENTHESIS", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10630", description :: Text
description = Text
"RIGHT WHITE PARENTHESIS", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10631", description :: Text
description = Text
"Z NOTATION LEFT IMAGE BRACKET", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10632", description :: Text
description = Text
"Z NOTATION RIGHT IMAGE BRACKET", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10633", description :: Text
description = Text
"Z NOTATION LEFT BINDING BRACKET", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10634", description :: Text
description = Text
"Z NOTATION RIGHT BINDING BRACKET", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10635", description :: Text
description = Text
"LEFT SQUARE BRACKET WITH UNDERBAR", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10636", description :: Text
description = Text
"RIGHT SQUARE BRACKET WITH UNDERBAR", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10637", description :: Text
description = Text
"LEFT SQUARE BRACKET WITH TICK IN TOP CORNER", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10638", description :: Text
description = Text
"RIGHT SQUARE BRACKET WITH TICK IN BOTTOM CORNER", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10639", description :: Text
description = Text
"LEFT SQUARE BRACKET WITH TICK IN BOTTOM CORNER", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10640", description :: Text
description = Text
"RIGHT SQUARE BRACKET WITH TICK IN TOP CORNER", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10641", description :: Text
description = Text
"LEFT ANGLE BRACKET WITH DOT", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10642", description :: Text
description = Text
"RIGHT ANGLE BRACKET WITH DOT", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10643", description :: Text
description = Text
"LEFT ARC LESS-THAN BRACKET", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10644", description :: Text
description = Text
"RIGHT ARC GREATER-THAN BRACKET", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10645", description :: Text
description = Text
"DOUBLE LEFT ARC GREATER-THAN BRACKET", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10646", description :: Text
description = Text
"DOUBLE RIGHT ARC LESS-THAN BRACKET", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10647", description :: Text
description = Text
"LEFT BLACK TORTOISE SHELL BRACKET", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10648", description :: Text
description = Text
"RIGHT BLACK TORTOISE SHELL BRACKET", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10649", description :: Text
description = Text
"DOTTED FENCE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10650", description :: Text
description = Text
"VERTICAL ZIGZAG LINE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10651", description :: Text
description = Text
"MEASURED ANGLE OPENING LEFT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10652", description :: Text
description = Text
"RIGHT ANGLE VARIANT WITH SQUARE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10653", description :: Text
description = Text
"MEASURED RIGHT ANGLE WITH DOT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10654", description :: Text
description = Text
"ANGLE WITH S INSIDE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10655", description :: Text
description = Text
"ACUTE ANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10656", description :: Text
description = Text
"SPHERICAL ANGLE OPENING LEFT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10657", description :: Text
description = Text
"SPHERICAL ANGLE OPENING UP", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10658", description :: Text
description = Text
"TURNED ANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10659", description :: Text
description = Text
"REVERSED ANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10660", description :: Text
description = Text
"ANGLE WITH UNDERBAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10661", description :: Text
description = Text
"REVERSED ANGLE WITH UNDERBAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10662", description :: Text
description = Text
"OBLIQUE ANGLE OPENING UP", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10663", description :: Text
description = Text
"OBLIQUE ANGLE OPENING DOWN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10664", description :: Text
description = Text
"MEASURED ANGLE WITH OPEN ARM ENDING IN ARROW POINTING UP AND RIGHT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10665", description :: Text
description = Text
"MEASURED ANGLE WITH OPEN ARM ENDING IN ARROW POINTING UP AND LEFT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10666", description :: Text
description = Text
"MEASURED ANGLE WITH OPEN ARM ENDING IN ARROW POINTING DOWN AND RIGHT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10667", description :: Text
description = Text
"MEASURED ANGLE WITH OPEN ARM ENDING IN ARROW POINTING DOWN AND LEFT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10668", description :: Text
description = Text
"MEASURED ANGLE WITH OPEN ARM ENDING IN ARROW POINTING RIGHT AND UP", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10669", description :: Text
description = Text
"MEASURED ANGLE WITH OPEN ARM ENDING IN ARROW POINTING LEFT AND UP", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10670", description :: Text
description = Text
"MEASURED ANGLE WITH OPEN ARM ENDING IN ARROW POINTING RIGHT AND DOWN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10671", description :: Text
description = Text
"MEASURED ANGLE WITH OPEN ARM ENDING IN ARROW POINTING LEFT AND DOWN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10672", description :: Text
description = Text
"REVERSED EMPTY SET", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10673", description :: Text
description = Text
"EMPTY SET WITH OVERBAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10674", description :: Text
description = Text
"EMPTY SET WITH SMALL CIRCLE ABOVE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10675", description :: Text
description = Text
"EMPTY SET WITH RIGHT ARROW ABOVE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10676", description :: Text
description = Text
"EMPTY SET WITH LEFT ARROW ABOVE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10677", description :: Text
description = Text
"CIRCLE WITH HORIZONTAL BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10678", description :: Text
description = Text
"CIRCLED VERTICAL BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10679", description :: Text
description = Text
"CIRCLED PARALLEL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10680", description :: Text
description = Text
"CIRCLED REVERSE SOLIDUS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10681", description :: Text
description = Text
"CIRCLED PERPENDICULAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10682", description :: Text
description = Text
"CIRCLE DIVIDED BY HORIZONTAL BAR AND TOP HALF DIVIDED BY VERTICAL BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10683", description :: Text
description = Text
"CIRCLE WITH SUPERIMPOSED X", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10684", description :: Text
description = Text
"CIRCLED ANTICLOCKWISE-ROTATED DIVISION SIGN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10685", description :: Text
description = Text
"UP ARROW THROUGH CIRCLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10686", description :: Text
description = Text
"CIRCLED WHITE BULLET", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10687", description :: Text
description = Text
"CIRCLED BULLET", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10688", description :: Text
description = Text
"CIRCLED LESS-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10689", description :: Text
description = Text
"CIRCLED GREATER-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10690", description :: Text
description = Text
"CIRCLE WITH SMALL CIRCLE TO THE RIGHT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10691", description :: Text
description = Text
"CIRCLE WITH TWO HORIZONTAL STROKES TO THE RIGHT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10692", description :: Text
description = Text
"SQUARED RISING DIAGONAL SLASH", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10693", description :: Text
description = Text
"SQUARED FALLING DIAGONAL SLASH", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10694", description :: Text
description = Text
"SQUARED ASTERISK", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10695", description :: Text
description = Text
"SQUARED SMALL CIRCLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10696", description :: Text
description = Text
"SQUARED SQUARE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10697", description :: Text
description = Text
"TWO JOINED SQUARES", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10698", description :: Text
description = Text
"TRIANGLE WITH DOT ABOVE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10699", description :: Text
description = Text
"TRIANGLE WITH UNDERBAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10700", description :: Text
description = Text
"S IN TRIANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10701", description :: Text
description = Text
"TRIANGLE WITH SERIFS AT BOTTOM", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10702", description :: Text
description = Text
"RIGHT TRIANGLE ABOVE LEFT TRIANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10703", description :: Text
description = Text
"LEFT TRIANGLE BESIDE VERTICAL BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10703\824", description :: Text
description = Text
"LEFT TRIANGLE BESIDE VERTICAL BAR with slash", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10704", description :: Text
description = Text
"VERTICAL BAR BESIDE RIGHT TRIANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10704\824", description :: Text
description = Text
"VERTICAL BAR BESIDE RIGHT TRIANGLE with slash", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10705", description :: Text
description = Text
"BOWTIE WITH LEFT HALF BLACK", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10706", description :: Text
description = Text
"BOWTIE WITH RIGHT HALF BLACK", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10707", description :: Text
description = Text
"BLACK BOWTIE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10708", description :: Text
description = Text
"TIMES WITH LEFT HALF BLACK", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10709", description :: Text
description = Text
"TIMES WITH RIGHT HALF BLACK", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10710", description :: Text
description = Text
"WHITE HOURGLASS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10711", description :: Text
description = Text
"BLACK HOURGLASS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10712", description :: Text
description = Text
"LEFT WIGGLY FENCE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10713", description :: Text
description = Text
"RIGHT WIGGLY FENCE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10715", description :: Text
description = Text
"RIGHT DOUBLE WIGGLY FENCE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10716", description :: Text
description = Text
"INCOMPLETE INFINITY", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10717", description :: Text
description = Text
"TIE OVER INFINITY", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10718", description :: Text
description = Text
"INFINITY NEGATED WITH VERTICAL BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10719", description :: Text
description = Text
"DOUBLE-ENDED MULTIMAP", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10720", description :: Text
description = Text
"SQUARE WITH CONTOURED OUTLINE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10721", description :: Text
description = Text
"INCREASES AS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10722", description :: Text
description = Text
"SHUFFLE PRODUCT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10723", description :: Text
description = Text
"EQUALS SIGN AND SLANTED PARALLEL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10724", description :: Text
description = Text
"EQUALS SIGN AND SLANTED PARALLEL WITH TILDE ABOVE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10725", description :: Text
description = Text
"IDENTICAL TO AND SLANTED PARALLEL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10726", description :: Text
description = Text
"GLEICH STARK", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10727", description :: Text
description = Text
"THERMODYNAMIC", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10728", description :: Text
description = Text
"DOWN-POINTING TRIANGLE WITH LEFT HALF BLACK", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10729", description :: Text
description = Text
"DOWN-POINTING TRIANGLE WITH RIGHT HALF BLACK", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10730", description :: Text
description = Text
"BLACK DIAMOND WITH DOWN ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10731", description :: Text
description = Text
"BLACK LOZENGE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10732", description :: Text
description = Text
"WHITE CIRCLE WITH DOWN ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10733", description :: Text
description = Text
"BLACK CIRCLE WITH DOWN ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10734", description :: Text
description = Text
"ERROR-BARRED WHITE SQUARE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10735", description :: Text
description = Text
"ERROR-BARRED BLACK SQUARE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10736", description :: Text
description = Text
"ERROR-BARRED WHITE DIAMOND", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10737", description :: Text
description = Text
"ERROR-BARRED BLACK DIAMOND", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10738", description :: Text
description = Text
"ERROR-BARRED WHITE CIRCLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10739", description :: Text
description = Text
"ERROR-BARRED BLACK CIRCLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10740", description :: Text
description = Text
"RULE-DELAYED", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10741", description :: Text
description = Text
"REVERSE SOLIDUS OPERATOR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10742", description :: Text
description = Text
"SOLIDUS WITH OVERBAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10743", description :: Text
description = Text
"REVERSE SOLIDUS WITH HORIZONTAL STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10744", description :: Text
description = Text
"BIG SOLIDUS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10745", description :: Text
description = Text
"BIG REVERSE SOLIDUS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10746", description :: Text
description = Text
"DOUBLE PLUS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10747", description :: Text
description = Text
"TRIPLE PLUS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10748", description :: Text
description = Text
"LEFT-POINTING CURVED ANGLE BRACKET", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10749", description :: Text
description = Text
"RIGHT-POINTING CURVED ANGLE BRACKET", form :: FormType
form = FormType
FPostfix, priority :: Int
priority = Int
20, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"symmetric",Text
"fence",Text
"stretchy",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10750", description :: Text
description = Text
"TINY", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10751", description :: Text
description = Text
"MINY", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10752", description :: Text
description = Text
"N-ARY CIRCLED DOT OPERATOR", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
330, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"movablelimits"]}
  , Operator {oper :: Text
oper = Text
"\10753", description :: Text
description = Text
"N-ARY CIRCLED PLUS OPERATOR", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
300, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"movablelimits"]}
  , Operator {oper :: Text
oper = Text
"\10754", description :: Text
description = Text
"N-ARY CIRCLED TIMES OPERATOR", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
330, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"movablelimits"]}
  , Operator {oper :: Text
oper = Text
"\10755", description :: Text
description = Text
"N-ARY UNION OPERATOR WITH DOT", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
320, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"movablelimits"]}
  , Operator {oper :: Text
oper = Text
"\10756", description :: Text
description = Text
"N-ARY UNION OPERATOR WITH PLUS", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
320, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"movablelimits"]}
  , Operator {oper :: Text
oper = Text
"\10757", description :: Text
description = Text
"N-ARY SQUARE INTERSECTION OPERATOR", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
330, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"movablelimits"]}
  , Operator {oper :: Text
oper = Text
"\10758", description :: Text
description = Text
"N-ARY SQUARE UNION OPERATOR", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
330, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"movablelimits"]}
  , Operator {oper :: Text
oper = Text
"\10759", description :: Text
description = Text
"TWO LOGICAL AND OPERATOR", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
330, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"movablelimits"]}
  , Operator {oper :: Text
oper = Text
"\10760", description :: Text
description = Text
"TWO LOGICAL OR OPERATOR", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
330, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"movablelimits"]}
  , Operator {oper :: Text
oper = Text
"\10761", description :: Text
description = Text
"N-ARY TIMES OPERATOR", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
330, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"movablelimits"]}
  , Operator {oper :: Text
oper = Text
"\10762", description :: Text
description = Text
"MODULO TWO SUM", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
290, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"movablelimits",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10763", description :: Text
description = Text
"SUMMATION WITH INTEGRAL", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
290, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10764", description :: Text
description = Text
"QUADRUPLE INTEGRAL OPERATOR", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
310, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
1, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10765", description :: Text
description = Text
"FINITE PART INTEGRAL", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
310, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10766", description :: Text
description = Text
"INTEGRAL WITH DOUBLE STROKE", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
310, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10767", description :: Text
description = Text
"INTEGRAL AVERAGE WITH SLASH", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
310, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10768", description :: Text
description = Text
"CIRCULATION FUNCTION", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
310, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"movablelimits",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10769", description :: Text
description = Text
"ANTICLOCKWISE INTEGRATION", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
310, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"movablelimits",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10770", description :: Text
description = Text
"LINE INTEGRATION WITH RECTANGULAR PATH AROUND POLE", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
310, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"movablelimits",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10771", description :: Text
description = Text
"LINE INTEGRATION WITH SEMICIRCULAR PATH AROUND POLE", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
310, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"movablelimits",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10772", description :: Text
description = Text
"LINE INTEGRATION NOT INCLUDING THE POLE", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
310, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"movablelimits",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10773", description :: Text
description = Text
"INTEGRAL AROUND A POINT OPERATOR", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
310, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10774", description :: Text
description = Text
"QUATERNION INTEGRAL OPERATOR", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
310, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10775", description :: Text
description = Text
"INTEGRAL WITH LEFTWARDS ARROW WITH HOOK", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
310, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10776", description :: Text
description = Text
"INTEGRAL WITH TIMES SIGN", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
310, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10777", description :: Text
description = Text
"INTEGRAL WITH INTERSECTION", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
310, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10778", description :: Text
description = Text
"INTEGRAL WITH UNION", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
310, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10779", description :: Text
description = Text
"INTEGRAL WITH OVERBAR", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
310, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10780", description :: Text
description = Text
"INTEGRAL WITH UNDERBAR", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
310, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"mirrorable"]}
  , Operator {oper :: Text
oper = Text
"\10781", description :: Text
description = Text
"JOIN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10782", description :: Text
description = Text
"LARGE LEFT TRIANGLE OPERATOR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10783", description :: Text
description = Text
"Z NOTATION SCHEMA COMPOSITION", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10784", description :: Text
description = Text
"Z NOTATION SCHEMA PIPING", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10785", description :: Text
description = Text
"Z NOTATION SCHEMA PROJECTION", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10786", description :: Text
description = Text
"PLUS SIGN WITH SMALL CIRCLE ABOVE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10787", description :: Text
description = Text
"PLUS SIGN WITH CIRCUMFLEX ACCENT ABOVE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10788", description :: Text
description = Text
"PLUS SIGN WITH TILDE ABOVE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10789", description :: Text
description = Text
"PLUS SIGN WITH DOT BELOW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10790", description :: Text
description = Text
"PLUS SIGN WITH TILDE BELOW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10791", description :: Text
description = Text
"PLUS SIGN WITH SUBSCRIPT TWO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10792", description :: Text
description = Text
"PLUS SIGN WITH BLACK TRIANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10793", description :: Text
description = Text
"MINUS SIGN WITH COMMA ABOVE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10794", description :: Text
description = Text
"MINUS SIGN WITH DOT BELOW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10795", description :: Text
description = Text
"MINUS SIGN WITH FALLING DOTS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10796", description :: Text
description = Text
"MINUS SIGN WITH RISING DOTS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10797", description :: Text
description = Text
"PLUS SIGN IN LEFT HALF CIRCLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10798", description :: Text
description = Text
"PLUS SIGN IN RIGHT HALF CIRCLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10799", description :: Text
description = Text
"VECTOR OR CROSS PRODUCT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
390, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10800", description :: Text
description = Text
"MULTIPLICATION SIGN WITH DOT ABOVE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10801", description :: Text
description = Text
"MULTIPLICATION SIGN WITH UNDERBAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10802", description :: Text
description = Text
"SEMIDIRECT PRODUCT WITH BOTTOM CLOSED", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10803", description :: Text
description = Text
"SMASH PRODUCT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10804", description :: Text
description = Text
"MULTIPLICATION SIGN IN LEFT HALF CIRCLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10805", description :: Text
description = Text
"MULTIPLICATION SIGN IN RIGHT HALF CIRCLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10806", description :: Text
description = Text
"CIRCLED MULTIPLICATION SIGN WITH CIRCUMFLEX ACCENT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10807", description :: Text
description = Text
"MULTIPLICATION SIGN IN DOUBLE CIRCLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10808", description :: Text
description = Text
"CIRCLED DIVISION SIGN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10809", description :: Text
description = Text
"PLUS SIGN IN TRIANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10810", description :: Text
description = Text
"MINUS SIGN IN TRIANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10811", description :: Text
description = Text
"MULTIPLICATION SIGN IN TRIANGLE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10812", description :: Text
description = Text
"INTERIOR PRODUCT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10813", description :: Text
description = Text
"RIGHTHAND INTERIOR PRODUCT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10814", description :: Text
description = Text
"Z NOTATION RELATIONAL COMPOSITION", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10815", description :: Text
description = Text
"AMALGAMATION OR COPRODUCT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
390, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10816", description :: Text
description = Text
"INTERSECTION WITH DOT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10817", description :: Text
description = Text
"UNION WITH MINUS SIGN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10818", description :: Text
description = Text
"UNION WITH OVERBAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10819", description :: Text
description = Text
"INTERSECTION WITH OVERBAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10820", description :: Text
description = Text
"INTERSECTION WITH LOGICAL AND", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10821", description :: Text
description = Text
"UNION WITH LOGICAL OR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10822", description :: Text
description = Text
"UNION ABOVE INTERSECTION", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10823", description :: Text
description = Text
"INTERSECTION ABOVE UNION", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10824", description :: Text
description = Text
"UNION ABOVE BAR ABOVE INTERSECTION", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10825", description :: Text
description = Text
"INTERSECTION ABOVE BAR ABOVE UNION", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10826", description :: Text
description = Text
"UNION BESIDE AND JOINED WITH UNION", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10827", description :: Text
description = Text
"INTERSECTION BESIDE AND JOINED WITH INTERSECTION", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10828", description :: Text
description = Text
"CLOSED UNION WITH SERIFS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10829", description :: Text
description = Text
"CLOSED INTERSECTION WITH SERIFS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10830", description :: Text
description = Text
"DOUBLE SQUARE INTERSECTION", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10831", description :: Text
description = Text
"DOUBLE SQUARE UNION", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10832", description :: Text
description = Text
"CLOSED UNION WITH SERIFS AND SMASH PRODUCT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10833", description :: Text
description = Text
"LOGICAL AND WITH DOT ABOVE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10834", description :: Text
description = Text
"LOGICAL OR WITH DOT ABOVE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10835", description :: Text
description = Text
"DOUBLE LOGICAL AND", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10836", description :: Text
description = Text
"DOUBLE LOGICAL OR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10837", description :: Text
description = Text
"TWO INTERSECTING LOGICAL AND", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10838", description :: Text
description = Text
"TWO INTERSECTING LOGICAL OR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10839", description :: Text
description = Text
"SLOPING LARGE OR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10840", description :: Text
description = Text
"SLOPING LARGE AND", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10841", description :: Text
description = Text
"LOGICAL OR OVERLAPPING LOGICAL AND", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10842", description :: Text
description = Text
"LOGICAL AND WITH MIDDLE STEM", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10843", description :: Text
description = Text
"LOGICAL OR WITH MIDDLE STEM", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10844", description :: Text
description = Text
"LOGICAL AND WITH HORIZONTAL DASH", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10845", description :: Text
description = Text
"LOGICAL OR WITH HORIZONTAL DASH", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10846", description :: Text
description = Text
"LOGICAL AND WITH DOUBLE OVERBAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10847", description :: Text
description = Text
"LOGICAL AND WITH UNDERBAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10848", description :: Text
description = Text
"LOGICAL AND WITH DOUBLE UNDERBAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10849", description :: Text
description = Text
"SMALL VEE WITH UNDERBAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10850", description :: Text
description = Text
"LOGICAL OR WITH DOUBLE OVERBAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10851", description :: Text
description = Text
"LOGICAL OR WITH DOUBLE UNDERBAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10852", description :: Text
description = Text
"Z NOTATION DOMAIN ANTIRESTRICTION", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10853", description :: Text
description = Text
"Z NOTATION RANGE ANTIRESTRICTION", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10854", description :: Text
description = Text
"EQUALS SIGN WITH DOT BELOW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10855", description :: Text
description = Text
"IDENTICAL WITH DOT ABOVE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10856", description :: Text
description = Text
"TRIPLE HORIZONTAL BAR WITH DOUBLE VERTICAL STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10857", description :: Text
description = Text
"TRIPLE HORIZONTAL BAR WITH TRIPLE VERTICAL STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10858", description :: Text
description = Text
"TILDE OPERATOR WITH DOT ABOVE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10859", description :: Text
description = Text
"TILDE OPERATOR WITH RISING DOTS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10860", description :: Text
description = Text
"SIMILAR MINUS SIMILAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10861", description :: Text
description = Text
"CONGRUENT WITH DOT ABOVE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10862", description :: Text
description = Text
"EQUALS WITH ASTERISK", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10863", description :: Text
description = Text
"ALMOST EQUAL TO WITH CIRCUMFLEX ACCENT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10864", description :: Text
description = Text
"APPROXIMATELY EQUAL OR EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10865", description :: Text
description = Text
"EQUALS SIGN ABOVE PLUS SIGN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10866", description :: Text
description = Text
"PLUS SIGN ABOVE EQUALS SIGN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10867", description :: Text
description = Text
"EQUALS SIGN ABOVE TILDE OPERATOR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10868", description :: Text
description = Text
"DOUBLE COLON EQUAL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10869", description :: Text
description = Text
"TWO CONSECUTIVE EQUALS SIGNS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10870", description :: Text
description = Text
"THREE CONSECUTIVE EQUALS SIGNS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10871", description :: Text
description = Text
"EQUALS SIGN WITH TWO DOTS ABOVE AND TWO DOTS BELOW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10872", description :: Text
description = Text
"EQUIVALENT WITH FOUR DOTS ABOVE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10873", description :: Text
description = Text
"LESS-THAN WITH CIRCLE INSIDE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10874", description :: Text
description = Text
"GREATER-THAN WITH CIRCLE INSIDE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10875", description :: Text
description = Text
"LESS-THAN WITH QUESTION MARK ABOVE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10876", description :: Text
description = Text
"GREATER-THAN WITH QUESTION MARK ABOVE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10877", description :: Text
description = Text
"LESS-THAN OR SLANTED EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10877\824", description :: Text
description = Text
"LESS-THAN OR SLANTED EQUAL TO with slash", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10878", description :: Text
description = Text
"GREATER-THAN OR SLANTED EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10878\824", description :: Text
description = Text
"GREATER-THAN OR SLANTED EQUAL TO with slash", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10879", description :: Text
description = Text
"LESS-THAN OR SLANTED EQUAL TO WITH DOT INSIDE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10880", description :: Text
description = Text
"GREATER-THAN OR SLANTED EQUAL TO WITH DOT INSIDE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10881", description :: Text
description = Text
"LESS-THAN OR SLANTED EQUAL TO WITH DOT ABOVE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10882", description :: Text
description = Text
"GREATER-THAN OR SLANTED EQUAL TO WITH DOT ABOVE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10883", description :: Text
description = Text
"LESS-THAN OR SLANTED EQUAL TO WITH DOT ABOVE RIGHT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10884", description :: Text
description = Text
"GREATER-THAN OR SLANTED EQUAL TO WITH DOT ABOVE LEFT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10885", description :: Text
description = Text
"LESS-THAN OR APPROXIMATE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10886", description :: Text
description = Text
"GREATER-THAN OR APPROXIMATE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10887", description :: Text
description = Text
"LESS-THAN AND SINGLE-LINE NOT EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10888", description :: Text
description = Text
"GREATER-THAN AND SINGLE-LINE NOT EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10889", description :: Text
description = Text
"LESS-THAN AND NOT APPROXIMATE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10890", description :: Text
description = Text
"GREATER-THAN AND NOT APPROXIMATE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10891", description :: Text
description = Text
"LESS-THAN ABOVE DOUBLE-LINE EQUAL ABOVE GREATER-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10892", description :: Text
description = Text
"GREATER-THAN ABOVE DOUBLE-LINE EQUAL ABOVE LESS-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10893", description :: Text
description = Text
"LESS-THAN ABOVE SIMILAR OR EQUAL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10894", description :: Text
description = Text
"GREATER-THAN ABOVE SIMILAR OR EQUAL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10895", description :: Text
description = Text
"LESS-THAN ABOVE SIMILAR ABOVE GREATER-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10896", description :: Text
description = Text
"GREATER-THAN ABOVE SIMILAR ABOVE LESS-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10897", description :: Text
description = Text
"LESS-THAN ABOVE GREATER-THAN ABOVE DOUBLE-LINE EQUAL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10898", description :: Text
description = Text
"GREATER-THAN ABOVE LESS-THAN ABOVE DOUBLE-LINE EQUAL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10899", description :: Text
description = Text
"LESS-THAN ABOVE SLANTED EQUAL ABOVE GREATER-THAN ABOVE SLANTED EQUAL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10900", description :: Text
description = Text
"GREATER-THAN ABOVE SLANTED EQUAL ABOVE LESS-THAN ABOVE SLANTED EQUAL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10901", description :: Text
description = Text
"SLANTED EQUAL TO OR LESS-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10902", description :: Text
description = Text
"SLANTED EQUAL TO OR GREATER-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10903", description :: Text
description = Text
"SLANTED EQUAL TO OR LESS-THAN WITH DOT INSIDE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10904", description :: Text
description = Text
"SLANTED EQUAL TO OR GREATER-THAN WITH DOT INSIDE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10905", description :: Text
description = Text
"DOUBLE-LINE EQUAL TO OR LESS-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10906", description :: Text
description = Text
"DOUBLE-LINE EQUAL TO OR GREATER-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10907", description :: Text
description = Text
"DOUBLE-LINE SLANTED EQUAL TO OR LESS-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10908", description :: Text
description = Text
"DOUBLE-LINE SLANTED EQUAL TO OR GREATER-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10909", description :: Text
description = Text
"SIMILAR OR LESS-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10910", description :: Text
description = Text
"SIMILAR OR GREATER-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10911", description :: Text
description = Text
"SIMILAR ABOVE LESS-THAN ABOVE EQUALS SIGN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10912", description :: Text
description = Text
"SIMILAR ABOVE GREATER-THAN ABOVE EQUALS SIGN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10913", description :: Text
description = Text
"DOUBLE NESTED LESS-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10913\824", description :: Text
description = Text
"DOUBLE NESTED LESS-THAN with slash", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10914", description :: Text
description = Text
"DOUBLE NESTED GREATER-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10914\824", description :: Text
description = Text
"DOUBLE NESTED GREATER-THAN with slash", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10915", description :: Text
description = Text
"DOUBLE NESTED LESS-THAN WITH UNDERBAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10916", description :: Text
description = Text
"GREATER-THAN OVERLAPPING LESS-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10917", description :: Text
description = Text
"GREATER-THAN BESIDE LESS-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10918", description :: Text
description = Text
"LESS-THAN CLOSED BY CURVE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10919", description :: Text
description = Text
"GREATER-THAN CLOSED BY CURVE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10920", description :: Text
description = Text
"LESS-THAN CLOSED BY CURVE ABOVE SLANTED EQUAL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10921", description :: Text
description = Text
"GREATER-THAN CLOSED BY CURVE ABOVE SLANTED EQUAL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10922", description :: Text
description = Text
"SMALLER THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10923", description :: Text
description = Text
"LARGER THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10924", description :: Text
description = Text
"SMALLER THAN OR EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10925", description :: Text
description = Text
"LARGER THAN OR EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10926", description :: Text
description = Text
"EQUALS SIGN WITH BUMPY ABOVE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10927", description :: Text
description = Text
"PRECEDES ABOVE SINGLE-LINE EQUALS SIGN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10927\824", description :: Text
description = Text
"PRECEDES ABOVE SINGLE-LINE EQUALS SIGN with slash", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10928", description :: Text
description = Text
"SUCCEEDS ABOVE SINGLE-LINE EQUALS SIGN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10928\824", description :: Text
description = Text
"SUCCEEDS ABOVE SINGLE-LINE EQUALS SIGN with slash", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
260, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10929", description :: Text
description = Text
"PRECEDES ABOVE SINGLE-LINE NOT EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10930", description :: Text
description = Text
"SUCCEEDS ABOVE SINGLE-LINE NOT EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10931", description :: Text
description = Text
"PRECEDES ABOVE EQUALS SIGN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10932", description :: Text
description = Text
"SUCCEEDS ABOVE EQUALS SIGN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10933", description :: Text
description = Text
"PRECEDES ABOVE NOT EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10934", description :: Text
description = Text
"SUCCEEDS ABOVE NOT EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10935", description :: Text
description = Text
"PRECEDES ABOVE ALMOST EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10936", description :: Text
description = Text
"SUCCEEDS ABOVE ALMOST EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10937", description :: Text
description = Text
"PRECEDES ABOVE NOT ALMOST EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10938", description :: Text
description = Text
"SUCCEEDS ABOVE NOT ALMOST EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10939", description :: Text
description = Text
"DOUBLE PRECEDES", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10940", description :: Text
description = Text
"DOUBLE SUCCEEDS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10941", description :: Text
description = Text
"SUBSET WITH DOT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10942", description :: Text
description = Text
"SUPERSET WITH DOT", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10943", description :: Text
description = Text
"SUBSET WITH PLUS SIGN BELOW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10944", description :: Text
description = Text
"SUPERSET WITH PLUS SIGN BELOW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10945", description :: Text
description = Text
"SUBSET WITH MULTIPLICATION SIGN BELOW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10946", description :: Text
description = Text
"SUPERSET WITH MULTIPLICATION SIGN BELOW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10947", description :: Text
description = Text
"SUBSET OF OR EQUAL TO WITH DOT ABOVE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10948", description :: Text
description = Text
"SUPERSET OF OR EQUAL TO WITH DOT ABOVE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10949", description :: Text
description = Text
"SUBSET OF ABOVE EQUALS SIGN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10950", description :: Text
description = Text
"SUPERSET OF ABOVE EQUALS SIGN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10951", description :: Text
description = Text
"SUBSET OF ABOVE TILDE OPERATOR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10952", description :: Text
description = Text
"SUPERSET OF ABOVE TILDE OPERATOR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10953", description :: Text
description = Text
"SUBSET OF ABOVE ALMOST EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10954", description :: Text
description = Text
"SUPERSET OF ABOVE ALMOST EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10955", description :: Text
description = Text
"SUBSET OF ABOVE NOT EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10956", description :: Text
description = Text
"SUPERSET OF ABOVE NOT EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10957", description :: Text
description = Text
"SQUARE LEFT OPEN BOX OPERATOR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10958", description :: Text
description = Text
"SQUARE RIGHT OPEN BOX OPERATOR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10959", description :: Text
description = Text
"CLOSED SUBSET", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10960", description :: Text
description = Text
"CLOSED SUPERSET", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10961", description :: Text
description = Text
"CLOSED SUBSET OR EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10962", description :: Text
description = Text
"CLOSED SUPERSET OR EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10963", description :: Text
description = Text
"SUBSET ABOVE SUPERSET", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10964", description :: Text
description = Text
"SUPERSET ABOVE SUBSET", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10965", description :: Text
description = Text
"SUBSET ABOVE SUBSET", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10966", description :: Text
description = Text
"SUPERSET ABOVE SUPERSET", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10967", description :: Text
description = Text
"SUPERSET BESIDE SUBSET", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10968", description :: Text
description = Text
"SUPERSET BESIDE AND JOINED BY DASH WITH SUBSET", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10969", description :: Text
description = Text
"ELEMENT OF OPENING DOWNWARDS", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10970", description :: Text
description = Text
"PITCHFORK WITH TEE TOP", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10971", description :: Text
description = Text
"TRANSVERSAL INTERSECTION", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10973", description :: Text
description = Text
"NONFORKING", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10973\824", description :: Text
description = Text
"NONFORKING with slash", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10974", description :: Text
description = Text
"SHORT LEFT TACK", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10975", description :: Text
description = Text
"SHORT DOWN TACK", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10976", description :: Text
description = Text
"SHORT UP TACK", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10977", description :: Text
description = Text
"PERPENDICULAR WITH S", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10978", description :: Text
description = Text
"VERTICAL BAR TRIPLE RIGHT TURNSTILE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10979", description :: Text
description = Text
"DOUBLE VERTICAL BAR LEFT TURNSTILE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10980", description :: Text
description = Text
"VERTICAL BAR DOUBLE LEFT TURNSTILE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10981", description :: Text
description = Text
"DOUBLE VERTICAL BAR DOUBLE LEFT TURNSTILE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10982", description :: Text
description = Text
"LONG DASH FROM LEFT MEMBER OF DOUBLE VERTICAL", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10983", description :: Text
description = Text
"SHORT DOWN TACK WITH OVERBAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10984", description :: Text
description = Text
"SHORT UP TACK WITH UNDERBAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10985", description :: Text
description = Text
"SHORT UP TACK ABOVE SHORT DOWN TACK", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10986", description :: Text
description = Text
"DOUBLE DOWN TACK", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10987", description :: Text
description = Text
"DOUBLE UP TACK", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10988", description :: Text
description = Text
"DOUBLE STROKE NOT SIGN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10989", description :: Text
description = Text
"REVERSED DOUBLE STROKE NOT SIGN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10990", description :: Text
description = Text
"DOES NOT DIVIDE WITH REVERSED NEGATION SLASH", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10991", description :: Text
description = Text
"VERTICAL LINE WITH CIRCLE ABOVE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10992", description :: Text
description = Text
"VERTICAL LINE WITH CIRCLE BELOW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10993", description :: Text
description = Text
"DOWN TACK WITH CIRCLE BELOW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10994", description :: Text
description = Text
"PARALLEL WITH HORIZONTAL STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10995", description :: Text
description = Text
"PARALLEL WITH TILDE OPERATOR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10996", description :: Text
description = Text
"TRIPLE VERTICAL BAR BINARY RELATION", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10997", description :: Text
description = Text
"TRIPLE VERTICAL BAR WITH HORIZONTAL STROKE", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10998", description :: Text
description = Text
"TRIPLE COLON OPERATOR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\10999", description :: Text
description = Text
"TRIPLE NESTED LESS-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\11000", description :: Text
description = Text
"TRIPLE NESTED GREATER-THAN", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\11001", description :: Text
description = Text
"DOUBLE-LINE SLANTED LESS-THAN OR EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\11002", description :: Text
description = Text
"DOUBLE-LINE SLANTED GREATER-THAN OR EQUAL TO", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\11003", description :: Text
description = Text
"TRIPLE SOLIDUS BINARY RELATION", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\11004", description :: Text
description = Text
"LARGE TRIPLE VERTICAL BAR OPERATOR", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
330, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"movablelimits"]}
  , Operator {oper :: Text
oper = Text
"\11005", description :: Text
description = Text
"DOUBLE SOLIDUS OPERATOR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
4, rspace :: Int
rspace = Int
4, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\11006", description :: Text
description = Text
"WHITE VERTICAL BAR", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
265, lspace :: Int
lspace = Int
3, rspace :: Int
rspace = Int
3, properties :: [Text]
properties = []}
  , Operator {oper :: Text
oper = Text
"\11007", description :: Text
description = Text
"N-ARY WHITE VERTICAL BAR", form :: FormType
form = FormType
FPrefix, priority :: Int
priority = Int
330, lspace :: Int
lspace = Int
1, rspace :: Int
rspace = Int
2, properties :: [Text]
properties = [Text
"symmetric",Text
"largeop",Text
"movablelimits"]}
  , Operator {oper :: Text
oper = Text
"\11077", description :: Text
description = Text
"LEFTWARDS QUADRUPLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\11078", description :: Text
description = Text
"RIGHTWARDS QUADRUPLE ARROW", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
270, lspace :: Int
lspace = Int
5, rspace :: Int
rspace = Int
5, properties :: [Text]
properties = [Text
"stretchy"]}
  , Operator {oper :: Text
oper = Text
"\65079", description :: Text
description = Text
"PRESENTATION FORM FOR VERTICAL LEFT CURLY BRACKET", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}
  , Operator {oper :: Text
oper = Text
"\65080", description :: Text
description = Text
"PRESENTATION FORM FOR VERTICAL RIGHT CURLY BRACKET", form :: FormType
form = FormType
FInfix, priority :: Int
priority = Int
880, lspace :: Int
lspace = Int
0, rspace :: Int
rspace = Int
0, properties :: [Text]
properties = [Text
"stretchy",Text
"accent"]}]