Annotation of OpenXM/src/asir-contrib/packages/doc/mt_gkz/mt_gkz-en.texi, Revision 1.3
1.3 ! takayama 1: %% $OpenXM: OpenXM/src/asir-contrib/packages/doc/mt_gkz/mt_gkz-en.texi,v 1.2 2021/01/20 08:17:54 takayama Exp $
1.1 takayama 2: %% xetex mt_gkz-en.texi (.texi までつける. )
3: %% @math{tex形式の数式}
4: %% 参考: http://www.fan.gr.jp/~ring/doc/texinfo/texinfo-ja_14.html#SEC183
5: %% @tex{tex形式で書いたもの}
6: %%https://www.gnu.org/software/texinfo/manual/texinfo/html_node/_0040TeX-_0040LaTeX.html
7:
8: %% 英語版, 以下コメントは @comment で始める. \input texinfo 以降は普通の tex 命令は使えない.
9: \input texinfo-ja
10: @iftex
11: @catcode`@#=6
12: @def@fref#1{@xrefX[#1,,@code{#1},,,]}
13: @def@b#1{{@bf #1}}
14: @catcode`@#=@other
15: @end iftex
16: @overfullrule=0pt
17: @documentlanguage en
18: @c -*-texinfo-*-
19: @comment --- おまじない終り ---
20:
21: @comment --- GNU info ファイルの名前 ---
22: @setfilename mt_gkz_man
23:
24: @comment --- タイトル ---
25: @settitle GKZ hypergeometric system
26:
27: @comment --- おまじない ---
28: @ifinfo
29: @macro fref{name}
30: @ref{\name\,,@code{\name\}}
31: @end macro
32: @end ifinfo
33:
34: @titlepage
35: @comment --- おまじない終り ---
36:
37: @comment --- タイトル, バージョン, 著者名, 著作権表示 ---
38: @title GKZ hypergeometric system
39: @subtitle Pfaffian system (Pfaff equation), contiguity relations, cohomology intersection
40: @subtitle Version 1.0
41: @subtitle January 20, 2021
42:
43: @author by S-J. Matsubara-Heo, N.Takayama
44: @page
45: @vskip 0pt plus 1filll
46: Copyright @copyright{} Risa/Asir committers
47: 2004--2020. All rights reserved.
48: @end titlepage
49:
50: @comment --- おまじない ---
51: @synindex vr fn
52: @comment --- おまじない終り ---
53:
54: @comment --- @node は GNU info, HTML 用 ---
55: @comment --- @node の引数は node-name, next, previous, up ---
56: @node Top,, (dir), (dir)
57:
58: @comment --- @menu は GNU info, HTML 用 ---
59: @comment --- chapter 名を正確に並べる ---
60:
61: @menu
62: * About this document::
63: * Pfaff equation::
64: * b function::
65: * Utilities::
66: * Index::
67: @end menu
68:
69: @comment --- chapter の開始 ---
70: @comment --- 親 chapter 名を正確に. 親がない場合は Top ---
71: @node About this document,,, Top
72: @chapter About this document
73:
74: This document explains Risa/Asir functions for GKZ hypergeometric system
75: (A-hypergeometric system). @* @comment 強制改行
76: Loading the package:
77: @example
78: import("mt_gkz.rr");
79: @end example
80: @noindent
81: References cited in this document.
82: @itemize @bullet
83: @item [MT2020]
84: Saiei-Jaeyeong Matsubara-Heo, Nobuki Takayama,
85: Algorithms for Pfaffian Systems and Cohomology Intersection Numbers of Hypergeometric Integrals,
86: Lecture Notes in Computer Science 12097 (2020), 73--84.
87: Errata is posted on @uref{http://arxiv.org/abs/???}.
88: E-attachments can be obtainable at
89: @uref{http://www.math.kobe-u.ac.jp/OpenXM/Math/intersection2}
90: @item [GM2020]
91: Yoshiaki Goto, Saiei-Jaeyeong Matsubara-Heo,
92: Homology and cohomology intersection numbers of GKZ systems, arXiv:2006.07848
93: @item [SST1999]
94: M.Saito, B.Sturmfels, N.Takayama, Hypergeometric polynomials
95: and integer programming, Compositio Mathematica, 155 (1999), 185--204
96: @item [SST2000]
97: M.Saito, B.Sturmfels, N.Takayama, Groebner Deformations of Hypergeometric
98: Differential Equations. Springer, 2000.
99: @end itemize
100:
101: References for maple packages IntegrableConnections and OreMorphisms.
102: @itemize @bullet
103: @item [BCEW]
104: M.Barkatou, T.Cluzeau, C.El Bacha, J.-A.Weil,
105: IntegrableConnections – a maple package for computing closed form solutions of integrable connections
106: (2012). @uref{https://www.unilim.fr/pages perso/thomas.cluzeau/Packages/IntegrableConnections/PDS.html}
107: @item [CQ]
108: T.Cluzeau and A.Quadrat,
109: OreMorphisms: A homological algebraic package for factoring, reducing and decomposing linear functional systems (2009). @uref{https://who.rocq.inria.fr/Alban.Quadrat/OreMorphisms/index.html}
110: @item [CQ08]
111: T.Cluzeau, A.Quadrat, Factoring and decomposing a class of linear functional
112: systems, Linear Algebra and its Applications (LAA), 428(1): 324-381, 2008.
113: @end itemize
114:
115:
116:
117: @node Pfaff equation,,, Top
118: @chapter Pfaff equation
119:
120: @menu
121: * mt_gkz.pfaff_eq::
122: * mt_gkz.ff::
123: * mt_gkz.ff1::
124: * mt_gkz.ff2::
125: * mt_gkz.rvec_to_fvec::
126: @end menu
127:
128: @node Pfaff equation for given cocycles,,, Pfaff equation
129: @section Pfaff equation for given cocycles
130:
131: @comment **********************************************************
132: @comment --- 関数 pfaff_eq
133: @node mt_gkz.pfaff_eq,,, Pfaff equation for given cocycles
134: @subsection @code{mt_gkz.pfaff_eq}
135: @comment --- 索引用キーワード
136: @findex mt_gkz.pfaff_eq
137:
138: @table @t
139: @item mt_gkz.pfaff_eq(@var{A},@var{Beta},@var{Ap},@var{Rvec},@var{DirX})
140: :: It returns the Pfaff equation for the GKZ system defined by @var{A} and @var{Beta} with respect to cocycles defined by @var{Rvec}.
141: @end table
142:
143: @comment --- 引数の簡単な説明 ---
144: @table @var
145: @item return
146: a list of coefficients of the Pfaff equation with respect to the direction @var{DirX}
147: @item A
148: the matrix A of the GKZ system.
149: @item Beta
150: the parameter vector of the GKZ system.
151: @item Ap
152: See [MT2020].
153: @item Rvec
154: It is used to specify a basis of cocycles. See [MT2020]
155: @item DirX
156: a list of dxi's.
157: @end table
158:
159: @comment --- ここで関数の詳しい説明 ---
160: @comment --- @itemize〜@end itemize は箇条書き ---
161: @comment --- @bullet は黒点付き ---
162: @itemize @bullet
163: @item
164: The independent variables are x1, x2, x3, ...
165: @item
166: When @var{Rvec}=[v_1, v_2, ..., v_r] where r is the rank of the GKZ system,
167: the set of the cocycles standing for Av_1, Av_2, ..., Av_r
168: (see [MT2020])
169: is supposed
170: to be the basis to construct the Pfaffian system.
171: Let a_1, a_2, ..., a_n be the column vectors of the matrix A
172: and v be a column vector (x_1, x_2, ..., x_n)^T.
173: Av is defined as a_1 x_1 + a_2 x_2 + ... + a_n x_n.
174: @item
175: When the columns of @var{A} are expressed as
176: @math{e_i \otimes \alpha_{i_j}},
177: the columns of @var{Ap} is
178: @math{e_i \otimes 0} where $e_i$ is the i-th unit vector.
179: See [MT2020] on the definition of @var{Ap}.
180: Here are some examples.
181: When @var{A} is
182: @verbatim
183: [[1,1,0,0],
184: [0,0,1,1],
185: [0,1,0,1]]
186: @end verbatim
187: @var{Ap} is
188: @verbatim
189: [[1,1,0,0],
190: [0,0,1,1],
191: [0,0,0,0]] <-- zero row
192: @end verbatim
193: When @var{A} is
194: @verbatim
195: [[1,1,1,0,0,0],
196: [0,0,0,1,1,1],
197: [0,1,0,0,1,0],
198: [0,0,1,0,0,1]
199: ]
200: @end verbatim
201: @var{Ap} is
202: @verbatim
203: [[1,1,1,0,0,0],
204: [0,0,0,1,1,1],
205: [0,0,0,0,0,0], <-- zero row
206: [0,0,0,0,0,0] <-- zero row
207: ]
208: @end verbatim
209: See also page 223 of [SST2000].
210: @item
211: Option @var{xrule}. When the option @var{xrule} is given,
212: the x variables specified by this option are specialized to numbers.
213: @item
214: Option @var{shift}. When the matrix @var{A} is not normal
215: (the associated toric ideal is not normal), a proper shift vector
216: must be given to obtain an element of the b-ideal. Or, use the option
217: @var{b_ideal} below. See [SST1999] on the theory.
218: @item
219: Option @var{b_ideal}. When the matrix @var{A} is not normal,
220: the option @code{b_ideal=1} obtains b-ideals and the first element
221: of each b-ideal is used as the b-function. The option @var{shift}
222: is ignored.
223: @item
224: Option @var{cg}. A constant matrix given by this option is used
225: for the Gauge transformation of the Pfaffian system.
226: In other words, the basis of cocycles specified by @var{Rvec}
227: is transformed by the constant matrix given by this option.
228: @end itemize
229:
230: @comment --- @example〜@end example は実行例の表示 ---
231: Example: Gauss hypergeometric system, see [GM2020] example ??.
232: @example
233: [1883] import("mt_gkz.rr");
234: [2657] PP=mt_gkz.pfaff_eq(A=[[1,1,0,0],[0,0,1,1],[0,1,0,1]],
235: Beta=[-g1,-g2,-c],
236: Ap = [[1,1,0,0],[0,0,1,1],[0,0,0,0]],
237: Rvec = [[1,0,0,0],[0,0,1,0]],
238: DirX=[dx4,dx3] | xrule=[[x1,1],[x2,1]],
239: cg=matrix_list_to_matrix([[1,0],[-1,1]]))$
240:
241: Bfunctions=[s_1*s_2-s_1*s_3+s_1^2,s_1*s_3,s_2^2+(-s_3+s_1)*s_2,s_3*s_2]
242: -- snip --
243: [2658] PP[0];
244: [ (g2*x3-g2)/(x4-x3) (g2*x3)/(x4-x3) ]
245: [ ((-g2*x3-c+g2)*x4+(c-g1)*x3+g1)/(x4^2-x3*x4)
246: ((-g2*x3-c)*x4+(c-g1)*x3)/(x4^2-x3*x4) ]
247: [2659] PP[1];
248: [ (-g2*x4+g2)/(x4-x3) (-g2*x4)/(x4-x3) ]
249: [ ((g2*x3+c-g2-1)*x4+(-c+g1+1)*x3-g1)/(x3*x4-x3^2)
250: ((g2*x3+c-g2-1)*x4+(-c+g1+g2+1)*x3)/(x3*x4-x3^2) ]
251: @end example
252:
253: @*
254:
255: Example: The role of shift.
256: When the toric ideal is not normal, a proper shift vector
257: must be given with the option @code{shift} to find an element of the b-ideal.
258: @example
259: [1882] load("mt_gkz.rr");
260: [1883] A=[[1,1,1,1],[0,1,3,4]];
261: [[1,1,1,1],[0,1,3,4]]
262: [1884] Ap=[[1,1,1,1],[0,0,0,0]];
263: [[1,1,1,1],[0,0,0,0]]
264: [1885] Rvec=[[0,0,0,0],[0,0,1,0],[0,0,0,1],[0,0,0,2]];
265: [[0,0,0,0],[0,0,1,0],[0,0,0,1],[0,0,0,2]];
266: [2674] P=mt_gkz.pfaff_eq(A,[b1,b2],Ap,Rvec,DirX=[dx4]
267: | xrule=[[x1,1],[x2,2],[x3,4]] )$
268: dx remains
269: stopped in step_up at line 342 in file "./mt_gkz/saito-b.rr"
270: 342 if (type(dn(Ans)) > 1) error("dx remains");
271: (debug) quit
272: // Since the toric ideal for A is not normal, it stops with the error.
273: [2675] P=mt_gkz.pfaff_eq(A,[b1,b2],Ap,Rvec,DirX=[dx4]
274: | shift=[1,0],xrule=[[x1,1],[x2,2],[x3,4]])$
275: // It works.
276: @end example
277:
278: @comment --- 参照(リンク)を書く ---
279: @table @t
280: @item Refer to
281: @ref{mt_gkz.ff1}
282: @ref{mt_gkz.ff2}
283: @ref{mt_gkz.ff}
284: @ref{mt_gkz.rvec_to_fvec}
285: @end table
286: @comment mt_gkz.pfaff_eq の説明おわり. あとはこれの繰り返し.
287:
288:
289: @comment --- 個々の関数の説明 ---
290: @comment --- section 名を正確に ---
291: @node mt_gkz.ff2,,, Pfaff equation for given cocycles
292: @node mt_gkz.ff1,,, Pfaff equation for given cocycles
293: @node mt_gkz.ff,,, Pfaff equation for given cocycles
294: @subsection @code{mt_gkz.ff2}, @code{mt_gkz.ff1}, @code{mt_gkz.ff}
295: @comment --- 索引用キーワード
296: @findex mt_gkz.ff2
297: @findex mt_gkz.ff1
298: @findex mt_gkz.ff
299:
300: @table @t
301: @item mt_gkz.ff(@var{Rvec0},@var{A},@var{Beta},@var{Ap})
302: @item mt_gkz.ff1(@var{Rvec0},@var{A},@var{Beta},@var{Ap})
303: @item mt_gkz.ff2(@var{Rvec0},@var{A},@var{Beta},@var{Ap},@var{BF},@var{C})
304: :: @code{ff} returns a differential operator whose action to 1 gives
305: the cocycle defined by @var{Rvec0}
306: @end table
307:
308: @comment --- 引数の簡単な説明 ---
309: @table @var
310: @item return
311: @code{ff} returns a differential operator whose action to 1 of @math{M_A(\beta)}
312: gives the cocycle defined by @var{Rvec0}.
313: @item return
314: @code{ff1} returns a composite of step-down operators for the positive part
315: of @var{Rvec0}
316: @item return
317: @code{ff2} returns a composite of step-up operators for the positive part
318: of @var{Rvec0}
319: @item Rvec0
320: An element of @var{Rvec} explained in @ref{mt_gkz.pfaff_eq}.
321: @item BF
322: the list of b-functions to all directions.
323: @item C
324: the list of the step up operators for all a_1, a_2, ..., a_n.
325: @end table
326: Other arguments are same with those of @code{pfaff_eq}.
327:
328: @comment --- ここで関数の詳しい説明 ---
329: @comment --- @itemize〜@end itemize は箇条書き ---
330: @comment --- @bullet は黒点付き ---
331: @itemize @bullet
332: @item
333: The function @code{ff} generates the list of b-functions and the list of
334: step up operators and store them in the cache variable.
335: They can be obtained by calling as @code{S=mt_gkz.get_bf_step_up()}
336: where S[0] is the list of b-functions and S[1] is the list of step up
337: operators.
338: Step up operators are obtained by the algorithm given in [SST1999].
339: @item
340: Option nf. When nf=1, the output operator is reduced to the normal form
341: with respect to the Groebner basis of the GKZ system of the graded reverse
342: lexicographic order.
343: @item
344: Option shift. See @ref{mt_gkz.pfaff_eq}.
345: @item
346: Internal info: The function @code{mt_gkz.bb} gives the constant so that
347: the step up and step down operators (contiguity operators) give
348: contiguity relations for the integral representation in [MT2020].
349: Note that @code{mt_gkz.ff1} and @code{mt_gkz.ff2} give contiguity
350: relations which are constant multiple of those for hypergeometric
351: polynomials.
352: @item
353: Internal info: @code{mt_gkz.step_up} generates step up operators
354: of [SST1999] from b-functions by utilizing @code{mt_gkz.bf2euler}
355: and @code{mt_gkz.toric}.
356: @end itemize
357:
358: @comment --- @example〜@end example は実行例の表示 ---
359: Example: Step up operators compatible with the integral representation in [MT2020].
360: The function hgpoly_res defined in @code{check-by-hgpoly.rr} returns
361: a multiple of the hypergeometric polynomial which agrees with
362: the residue times a power of @math{2\pi \sqrt{-1}}
363: of the integral representation.
364: See [SST1999].
365: @example
366: [1883] import("mt_gkz.rr")$
367: [3175] load("mt_gkz/check-by-hgpoly.rr")$
368: [3176] A=[[1,1,0,0],[0,0,1,1],[0,1,0,1]]$
369: [3177] B=newvect(3,[5,4,7])$ Ap=[[1,1,0,0],[0,0,1,1],[0,0,0,0]]$
370: [3179] Beta=[b1,b2,b3]$ R=[0,0,-1,0]$
371: [3180] F2=hgpoly_res(A,B,2); // HG polynomial. 2 is the number of e_i's.
372: 10*x1^2*x2^3*x4^4+20*x1*x2^4*x3*x4^3+6*x2^5*x3^2*x4^2
373: [3182] mt_gkz.ff(R,A,Ap,Beta); // the operator standing for R
374: (x3*x4*dx4+x3^2*dx3+x1*x4*dx2+x1*x3*dx1+x3)/(b1+b2-b3+1)
375: [3184] S=mt_gkz.get_bf_step_up(A); // b-function and non-reduced step up op's
376: [[ s_1*s_2-s_1*s_3+s_1^2 s_1*s_3 s_2^2+(-s_3+s_1)*s_2 s_3*s_2 ],
377: [ x2*x3*dx4+x1*x3*dx3+x1*x2*dx2+x1^2*dx1+x1
378: x2*x4*dx4+x1*x4*dx3+x2^2*dx2+x1*x2*dx1+x2
379: x3*x4*dx4+x3^2*dx3+x1*x4*dx2+x1*x3*dx1+x3
380: x4^2*dx4+x3*x4*dx3+x2*x4*dx2+x2*x3*dx1+x4 ]]
381: [3185] Fvec=mt_gkz.ff2(R,A,Beta,Ap,S[0],S[1]);
382: (x3*x4*dx4+x3^2*dx3+x1*x4*dx2+x1*x3*dx1+x3)/(b1+b2-b3+1)
383: [3188] Fvec = base_replace(Fvec,assoc(Beta,vtol(B)));
384: 1/3*x3*x4*dx4+1/3*x3^2*dx3+1/3*x1*x4*dx2+1/3*x1*x3*dx1+1/3*x3
385: [3189] R32d = odiff_act(Fvec,F2,[x1,x2,x3,x4]); // Act Fvec to the hg-poly
386: 10*x1^3*x2^2*x4^5+50*x1^2*x2^3*x3*x4^4+50*x1*x2^4*x3^2*x4^3+10*x2^5*x3^3*x4^2
387: [3190] red(R32d/hgpoly_res(A,B+newvect(3,[0,1,0]),2));
388: // R32d agrees with the HG polynomial with Beta=[5,4,7]+[0,1,0].
389: 1
390: @end example
391:
392: @comment --- 参照(リンク)を書く ---
393: @table @t
394: @item Refer to
395: @ref{mt_gkz.pfaff_eq}
396: @end table
397: @comment おわり.
398:
399: @comment --- 個々の関数の説明 --- Ref:2020-11-09-tw-cohom-progs.goodnotes
400: @comment --- section 名を正確に ---
401: @node mt_gkz.rvec_to_fvec,,, Pfaff equation for given cocycles
402: @subsection @code{mt_gkz.rvec_to_fvec}
403: @comment --- 索引用キーワード
404: @findex mt_gkz.rvec_to_fvec
405:
406: @table @t
407: @item mt_gkz.rvec_to_fvec(@var{Rvec},@var{A},@var{Ap},@var{Beta})
408: :: It returns a set of differential operators standing for @var{Rvec}.
409: @end table
410:
411: @comment --- 引数の簡単な説明 ---
412: @table @var
413: @item return
414: It returns a set of differential operators of which action to
415: @math{1 \in M_A(\beta)} give cocycles specified by @var{Rvec}.
416: @item A, Ap, Beta
417: Same with @ref{mt_gkz.pfaff_eq}
418: @end table
419:
420: @comment --- ここで関数の詳しい説明 ---
421: @comment --- @itemize〜@end itemize は箇条書き ---
422: @comment --- @bullet は黒点付き ---
423: @itemize @bullet
424: @item
425: Internal info: this function builds the set of operators by calling
426: @ref{mt_gkz.ff}.
427: @end itemize
428:
429: @comment --- @example〜@end example は実行例の表示 ---
430: Example: The following two expressions are congruent because
431: @math{2a_1-a_2-a_3+a_4=a_1} for this @code{A}.
432: @example
433: [1883] import("mt_gkz.rr");
434: [3191] mt_gkz.rvec_to_fvec([[2,-1,-1,1],[0,0,1,0]],
435: [[1,1,0,0],[0,0,1,1],[0,1,0,1]],
436: [[1,1,0,0],[0,0,1,1],[0,0,0,0]],[b1,b2,b3]);
437: [(x2*x3*x4^2*dx1^2*dx4^3+((x1*x3*x4^2+x2*x3^2*x4)*dx1^2*dx3
438: +(x1*x2*x4^2+x2^2*x3*x4)*dx1^2*dx2+(x1^2*x4^2+2*x1*x2*x3*x4+x2^2*x3^2)*dx1^3
439: +(x1*x4^2+3*x2*x3*x4)*dx1^2)*dx4^2+(x1*x3^2*x4*dx1^2*dx3^2
440: +((x1^2*x3*x4+x1*x2*x3^2)*dx1^3+(3*x1*x3*x4+x2*x3^2)*dx1^2)*dx3
441: +x1*x2^2*x4*dx1^2*dx2^2+((x1^2*x2*x4+x1*x2^2*x3)*dx1^3
442: +(3*x1*x2*x4+x2^2*x3)*dx1^2)*dx2+x1^2*x2*x3*dx1^4
443: +(x1^2*x4+3*x1*x2*x3)*dx1^3+(x1*x4+x2*x3)*dx1^2)*dx4)
444: /(b3*b2*b1^3+(b3*b2^2+(-b3^2-2*b3)*b2)*b1^2+(-b3*b2^2+(b3^2+b3)*b2)*b1),
445: (dx3)/(b2)]
446: [3192] mt_gkz.rvec_to_fvec([[1,0,0,0],[0,0,1,0]],
447: [[1,1,0,0],[0,0,1,1],[0,1,0,1]],
448: [[1,1,0,0],[0,0,1,1],[0,0,0,0]],[b1,b2,b3]);
449: [(dx1)/(b1),(dx3)/(b2)]
450: @end example
451:
452: @comment --- 参照(リンク)を書く ---
453: @table @t
454: @item Refer to
455: @ref{mt_gkz.pfaff_eq}
456: @end table
457: @comment おわり.
458:
459: @comment --- fvec_to_conn_mat
460: @comment --- section 名を正確に ---
461: @node mt_gkz.fvec_to_conn_mat,,, Pfaff equation for given cocycles
462: @subsection @code{mt_gkz.fvec_to_conn_mat}
463: @comment --- 索引用キーワード
464: @findex mt_gkz.fvec_to_conn_mat
465:
466: @table @t
467: @item mt_gkz.fvec_to_conn_mat(@var{Fvec},@var{A},@var{Beta},@var{DirX})
468: :: It returns the coefficient matrices of the basis
469: @var{Fvec} or @var{DirX}[I]*@var{Fvec} in terms of the set of the standard basis.
470: @end table
471:
472: @comment --- 引数の簡単な説明 ---
473: @table @var
474: @item return
475: It returns the coefficient matrices of the basis
476: @var{Fvec} or @var{DirX}[I]*@var{Fvec} in terms of the set of the standard basis of the Groebner basis explained below.
477: @item A Beta
478: Same with @ref{mt_gkz.pfaff_eq}.
479: @item DirX
480: When @var{DirX} is 1, this function returns the matrix which expresses
481: @var{Fvec} in terms of the set of the standard monomials of
482: the Groebner basis of the GKZ system in the ring of rational function
483: coefficients with respect to the graded reverse lexicographic order.
484: In other cases, it returns the coefficient matrices of
485: @var{DirX}[I]'s*@var{Fvec} in terms of the set of the standard basis of the Groebner basis.
486: @end table
487:
488: @comment --- ここで関数の詳しい説明 ---
489: @comment --- @itemize〜@end itemize は箇条書き ---
490: @comment --- @bullet は黒点付き ---
491: @itemize @bullet
492: @item
493: It utilizes a Groebner basis computation by the package @code{yang.rr}
494: and @code{yang.reduction} to obtain connection matrices.
495: @item
496: This function calls some utility functions
497: @code{mt_gkz.dmul(Op1,Op2,XvarList)} (multiplication of @code{Op1} and @code{Op2}
498: and @code{mt_gkz.index_vars(x,Start,End | no_=1)}
499: which generates indexed variables without the underbar ``_''.
500: @item
501: We note here some other utility functions in this section:
502: @code{mt_gkz.check_compatibility(P,Q,X,Y)},
503: which checkes if the sytem d/dX-P, d/dY-Q is compatible.
504: @end itemize
505:
506: @comment --- @example〜@end example は実行例の表示 ---
507: Example: The following example illustrates how mt_gkz.pfaff_eq
508: obtains connection matrices.
509: @example
510: [1883] import("mt_gkz.rr");
511: [3201] V=mt_gkz.index_vars(x,1,4 | no_=1);
512: [x1,x2,x3,x4]
513: [3202] mt_gkz.dmul(dx1,x1^2,V);
514: x1^2*dx1+2*x1
515: [3204] A=[[1,1,0,0],[0,0,1,1],[0,1,0,1]]$
516: Ap=[[1,1,0,0],[0,0,1,1],[0,0,0,0]]$
517: Beta= [b1,b2,b3]$
518: Rvec = [[1,0,0,0],[0,0,1,0]]$
519: Fvec = mt_gkz.rvec_to_fvec(Rvec,A,Ap,Beta)$
520: /* Express cocyles Rvec
521: by elements Fvec in the Weyl algebra by contiguity relations. */
522: Cg = matrix_list_to_matrix([[1,0],[1,-1]])$
523: [3208] NN=mt_gkz.fvec_to_conn_mat(Fvec,A,Beta,1);
524: // Express Fvec by the standard monomials Std=NN[1].
525: 1 ooo 2 .ooo
526: [[ (x4)/(b1*x1) (b1-b3)/(b1*x1) ]
527: [ (-x4)/(b1*x2) (1)/(x3) ],[dx4,1]]
528: [3209] Std=NN[1];
529: [dx4,1]
530: [3173] NN=NN[0];
531: [ (x4)/(b1*x1) (b1-b3)/(b1*x1) ]
532: [ (-x4)/(b2*x3) (1)/(x3) ]
533: [3174] NN1=mt_gkz.fvec_to_conn_mat(Fvec,A,Beta,dx1)[0];
534: // Express dx1*Fvec by the standard monomials Std.
535: 1 ooo 2 .ooo
536: [ ((2*b1+b2-b3-1)*x1*x4^2+(-b1+b3+1)*x2*x3*x4)/(b1*x1^3*x4-b1*x1^2*x2*x3)
537: ((b1^2+(-2*b3-1)*b1-b3*b2+b3^2+b3)*x1*x4
538: +(-b1^2+(2*b3+1)*b1-b3^2-b3)*x2*x3)/(b1*x1^3*x4-b1*x1^2*x2*x3) ]
539: [(b1 (-b1*x1*x4^2-b2*x2*x3*x4)/(b2*x1^2*x3*x4-b2*x1*x2*x3^2)
540: (b1*x1*x4+(-b1+b3)*x2*x3)/(x1^2*x3*x4-x1*x2*x3^2) ]
541: [3188] P1=map(red,Cg*NN1*matrix_inverse(NN)*matrix_inverse(Cg));
542: [ ((-b2*x3+(b1+b2-b3-1)*x1)*x4+(-b1+b3+1)*x2*x3)/(x1^2*x4-x1*x2*x3)
543: (b2*x3*x4)/(x1^2*x4-x1*x2*x3) ]
544: [ ((-b2*x3+(b2-b3-1)*x1)*x4+(-b1+b3+1)*x2*x3+b1*x1*x2)/(x1^2*x4-x1*x2*x3)
545: ((b2*x3+b1*x1)*x4)/(x1^2*x4-x1*x2*x3) ]
546:
547: [3191] mt_gkz.pfaff_eq(A,Beta,Ap,Rvec,[dx1]|cg=Cg)[0]-P1;
548: [ 0 0 ]
549: [ 0 0 ] // P1 agrees with the output of mt_gkz.pfaff_eq.
550: @end example
551:
552: @comment --- 参照(リンク)を書く ---
553: @table @t
554: @item Refer to
555: @ref{mt_gkz.pfaff_eq}
556: @end table
557: @comment おわり.
558:
559: @comment ---------- New Chapter ---------------
560: @node b function,,, Top
561: @chapter b function
562:
563: @menu
564: * mt_gkz.bf::
565: * mt_gkz.bf::
566: @end menu
567:
568: @node b function and facet polynomial,,, b function
569: @section b function and facet polynomial
570: @comment ------- bf
571: @comment **********************************************************
572: @comment --- 個々の関数の説明 ---
573: @comment --- section 名を正確に ---
574: @node mt_gkz.bf,,, b function and facet polynomial
575: @subsection @code{mt_gkz.bf}
576: @comment --- 索引用キーワード
577: @findex mt_gkz.bf
578:
579: @table @t
580: @item mt_gkz.bf(@var{A},@var{Facet_poly},@var{II0})
581: :: It returns the b-function with respect to the direction @var{II0}.
582: @end table
583:
584: @comment --- 引数の簡単な説明 ---
585: @table @var
586: @item return
587: It returns the b-function introduced Saito with respect to the direction @var{II0} in case of @var{A} is normal or an element of b-ideal when a proper shift vector is given in case of @var{A} is not normal.
588: @item A
589: the matrix A of the GKZ system.
590: @item Facet_poly
591: The set of facet polynomials of the convex hull of @var{A}.
592: @item II0
593: Direction expressed as 0, 1, 2, ... (not 1, 2, 3, ...) to obtain the b function.
594: @end table
595:
596: @comment --- ここで関数の詳しい説明 ---
597: @comment --- @itemize〜@end itemize は箇条書き ---
598: @comment --- @bullet は黒点付き ---
599: @itemize @bullet
600: @item
601: See [SST1999] on the b-function introduced Saito and b-ideal.
602: @item
603: The facet polynomial must be primitive.
604: @end itemize
605:
606: @comment --- @example〜@end example は実行例の表示 ---
607: Example:
608: @example
609: [1883] import("mt_gkz.rr");
610:
611: [3193] A;
612: [[1,1,0,0],[0,0,1,1],[0,1,0,1]]
613: [3194] Fpoly=mt_gkz.facet_poly(A);
614: [[s_3,s_1,s_2-s_3+s_1,s_2],[[0,0,1],[1,0,0],[1,1,-1],[0,1,0]]]
615: [3196] mt_gkz.bf(A,Fpoly,0);
616: s_1*s_2-s_1*s_3+s_1^2
617: [3197] mt_gkz.bf(A,Fpoly,1);
618: s_1*s_3
619: @end example
620:
621: @comment --- 参照(リンク)を書く ---
622: @table @t
623: @item Refer to
624: @ref{mt_gkz.ff}
625: @ref{mt_gkz.facet_poly}
626: @end table
627: @comment おわり.
628:
629: @comment ------ facet_poly
630: @comment --- 個々の関数の説明 ---
631: @comment --- section 名を正確に ---
632: @node mt_gkz.facet_polyl,,, b function and facet polynomial
633: @subsection @code{mt_gkz.facet_poly}
634: @comment --- 索引用キーワード
635: @findex mt_gkz.facet_poly
636:
637: @table @t
638: @item mt_gkz.facet_poly(@var{A})
639: :: It returns the set of facet polynomials and their normal vectors of
640: the cone defined by @var{A}.
641: @end table
642:
643: @comment --- 引数の簡単な説明 ---
644: @table @var
645: @item return
646: It returns the set of facet polynomials and their normal vectors of
647: the cone generated by the column vectors of the matrix @var{A}.
648: @item A
649: the matrix A of the GKZ system.
650: @end table
651:
652: @comment --- ここで関数の詳しい説明 ---
653: @comment --- @itemize〜@end itemize は箇条書き ---
654: @comment --- @bullet は黒点付き ---
655: @itemize @bullet
656: @item
657: The facet polynomial f is primitive. In other words,
658: all f(a_i) is integer and min f(a_i)=1 for a_i's not being on f=0.
659: where a_i is the i-th column vector of the matrix @var{A}.
660: It can be checked by @code{mt_gkz.is_primitive(At,Facets)}
661: where @var{At} is the transpose of @var{A} and
662: @var{Facets} is the second return value of this function.
663: @item
664: This function utilizes the system polymake @uref{https://polymake.org}
665: on our server.
666: @end itemize
667:
668: @comment --- @example〜@end example は実行例の表示 ---
669: Example:
670: @example
671: [1883] import("mt_gkz.rr");
672: [1884] mt_gkz.facet_poly([[1,1,1,1],[0,1,2,3]]);
673: oohg_native=0, oohg_curl=1
674: [[s_2,-s_2+3*s_1],[[0,1],[3,-1]]]
675: @end example
676:
677: @comment --- 参照(リンク)を書く ---
678: @table @t
679: @item Refer to
680: @ref{mt_gkz.bf}
681: @end table
682: @comment おわり.
683:
684: @comment ---------- New Chapter ---------------
685: @node utilities,,, Top
686: @chapter Utilities
687:
688: @menu
689: * mt_gkz.reduce_by_toric::
690: * mt_gkz.tk_base_equal::
691: * mt_gkz.dp_op_to_coef_vec::
692: * mt_gkz.yang_gkz_buch::
693: * mt_gkz.p_true_nf_rat::
694: * mt_gkz.mdiff::
695: * mt_gkz.dvar::
696: * mt_gkz.ord_xi::
697: * mt_gkz.get_check_fvec::
698: * mt_gkz.get_bf_step_up::
1.2 takayama 699: * mt_gkz.mytoric_ideal::
1.1 takayama 700: @end menu
701:
702: @node some utility functions,,, utilities
703: @section Some utility functions
704:
705: @node mt_gkz.reduce_by_toric,,, some utility functions
706: @node mt_gkz.tk_base_equal,,, some utility functions
707: @node mt_gkz.dp_op_to_coef_vec,,, some utility functions
708: @node mt_gkz.yang_gkz_buch,,, some utility functions
709: @node mt_gkz.p_true_nf_rat,,, some utility functions
710: @node mt_gkz.mdiff,,, some utility functions
711: @node mt_gkz.dvar,,, some utility functions
712: @node mt_gkz.ord_xi,,, some utility functions
713: @node mt_gkz.get_check_fvec,,, some utility functions
714: @node mt_gkz.get_bf_step_up,,, some utility functions
1.2 takayama 715: @node mt_gkz.mytoric_ideal,,, some utility functions
1.1 takayama 716:
717: @findex mt_gkz.reduce_by_toric
718: @findex mt_gkz.tk_base_equal
719: @findex mt_gkz.dp_op_to_coef_vec
720: @findex mt_gkz.yang_gkz_buch
721: @findex mt_gkz.p_true_nf_rat
722: @findex mt_gkz.mdiff
723: @findex mt_gkz.dvar
724: @findex mt_gkz.ord_xi
725: @findex mt_gkz.get_check_fvec
726: @findex mt_gkz.get_bf_step_up
1.2 takayama 727: @findex mt_gkz.mytoric_ideal
1.1 takayama 728:
729: @comment --- @example〜@end example は実行例の表示 ---
730: We only show examples on these functions. As for details, please see
731: the source code.
732: @example
733: [1883] import("mt_gkz.rr");
734: [2667] mt_gkz.dvar([x1,x2]); // it generates variables starting with d
735: [dx1,dx2]
736: [2669] mt_gkz.p_true_nf_rat((1/3)*x^3-1,[x^2-1],[x],0);
737: [x-3,3] // p_true_nf does not accept rational number coefficients
738: [2670] A=[[1,1,1,1],[0,1,3,4]];
739: [[1,1,1,1],[0,1,3,4]]
740: [2671] mt_gkz.reduce_by_toric(dx3^4,A);
741: dx1*dx4^3 // reduction by toric ideal defined by A
742: [2672] nk_toric.toric_ideal(A);
743: [-x1*x4+x2*x3,-x2*x4^2+x3^3,x2^2*x4-x1*x3^2,-x1^2*x3+x2^3]
744: [2673] mt_gkz.yang_gkz_buch(A,[b1,b2]); // Groebner basis of GKZ system by yang.rr
745: 1 o 2 ..o 3 ..oooooooo 4 o 6 ooo 9 o
746: [[[(x2)*<<0,1,0,0>>+(3*x3)*<<0,0,1,0>>+ ---snip ---*<<0,0,0,0>>,1]],
747: [dx1,dx2,dx3,dx4],
748: [(1)*<<0,0,0,2>>,(1)*<<0,0,1,0>>,(1)*<<0,0,0,1>>,(1)*<<0,0,0,0>>]]
749:
750: [2674] mt_gkz.dp_op_to_coef_vec([x1*<<1,0>>+x1*x2*<<0,1>>,x1+1],[<<1,0>>,<<0,1>>]);
751: // x1+1 is the denominator
752: [ (x1)/(x1+1) (x1*x2)/(x1+1) ]
753: [2675] mt_gkz.tk_base_is_equal([1,2],[1,2]);
754: 1
755: [2676] mt_gkz.tk_base_is_equal([1,2],[1,x,y]);
756: 0
757: [2677] mt_gkz.mdiff(sin(x),x,1);
758: cos(x)
759: [2678] mt_gkz.mdiff(sin(x),x,2); //2nd derivative
760: -sin(x)
761: [3164] mt_gkz.ord_xi(V=[x1,x2,x3],II=1);
762: // matrix to define graded lexicographic order so that V[II] is the smallest.
763: [ 1 1 1 ]
764: [ 0 -1 0 ]
765: [ -1 0 0 ]
766: [3166] load("mt_gkz/check-by-hgpoly.rr");
767: [3187] check_0123(); // check the pfaffian for the A below by hg-polynomial.
768: A=[[1,1,1,1],[0,1,2,3]]
769: Ap=[[1,1,1,1],[0,0,0,0]]
770: --- snip ---
771: Bfunctions= --- snip ---
772: 0 (vector) is expected:
773: [[ 0 0 0 ],[ 0 0 0 ]]
774: [3188] mt_gkz.get_check_fvec();
775: // get the basis of cocycles used in terms of differential operators.
776: [1,(dx4)/(b1),(dx4^2)/(b1^2-b1)]
777: [3189] mt_gkz.clear_bf();
778: 0
779: [3190] mt_gkz.get_bf_step_up(A=[[1,1,1,1],[0,1,2,3]]);
780: // b-functions and step-up operators.
781: // Option b_ideal=1 or shift=... may be used for non-normal case.
782: [[ -s_2^3+(9*s_1-3)*s_2^2+ ---snip---
783: -s_2^3+(3*s_1+1)*s_2^2-3*s_1*s_2 s_2^3-3*s_2^2+2*s_2 ],
784: [ x3^3*dx4^2+ ---snip---
785: 3*x3^2*x4*dx4^2+ --- snip---]]
1.2 takayama 786: [3191] mt_gkz.mytoric_ideal(0 | use_4ti2=1);
787: // 4ti2 is used to obtain a generator set of the toric ideal
788: // defined by the matrix A
789: [3192] mt_gkz.mytoric_ideal(0 | use_4ti2=0);
790: // A slower method is used to obtain a generator set of the toric ideal
791: // defined by the matrix A. 4ti2 is not needed. Default.
1.1 takayama 792: @end example
793:
794:
795:
796:
797:
798:
799:
800:
801:
802:
803:
804:
805:
806:
807:
808:
809:
810:
811:
812:
813:
814:
815:
816:
817:
818:
819:
820:
821:
822:
823:
824:
825:
826:
827:
828:
829:
830:
831:
832:
833:
834:
835:
836:
837:
838:
839:
840:
841:
842:
843:
844:
845:
846:
847:
848:
849: @comment ここから追加版
850:
851: @node Cohomology intersection numbers,,, Top
852: @chapter Cohomology intersection numbers
853:
854: @menu
855: * mt_gkz.kronecker_prd::
856: * mt_gkz.secondary_eq::
857: * mt_gkz.generate_maple_file_IC::
858: * mt_gkz.generate_maple_file_MR::
1.2 takayama 859: * mt_gkz.principal_normalizing_constant::
1.1 takayama 860: @end menu
861:
862:
863:
864:
865:
866:
867: @node Secondary equation,,, Cohomology intersection numbers
868: @section Secondary equation
869:
870: @comment **********************************************************
871: @comment --- 関数 pfaff_eq
872: @node mt_gkz.kronecker_prd,,, Secondary equation
873: @subsection @code{mt_gkz.kronecker_prd}
874: @comment --- 索引用キーワード
875: @findex mt_gkz.kronecker_prd
876:
877: @table @t
878: @item mt_gkz.kronecker_prd(@var{A},@var{B})
879: :: It returns the Kronecker product of @var{A} and @var{B}.
880: @end table
881:
882: @comment --- 引数の簡単な説明 ---
883: @table @var
884: @item return
1.2 takayama 885: a matrix which is equal to the Kronecker product of @var{A} and @var{B} (@uref{https://en.wikipedia.org/wiki/Kronecker_product}).
1.1 takayama 886: @item A,B
887: list
888: @end table
889:
890:
891: @comment --- @example〜@end example は実行例の表示 ---
892:
893: @example
894: [2644] A=[[a,b],[c,d]];
895: [[a,b],[c,d]]
896: [2645] B=[[e,f],[g,h]];
897: [[e,f],[g,h]]
1.2 takayama 898: [2646] mt_gkz.kronecker_prd(A,B);
1.1 takayama 899: [ e*a f*a e*b f*b ]
900: [ g*a h*a g*b h*b ]
901: [ e*c f*c e*d f*d ]
902: [ g*c h*c g*d h*d ]
903: @end example
904:
905:
906:
907:
908:
909:
910:
911:
912: @node mt_gkz.secondary_eq,,, Secondary equation
913: @subsection @code{mt_gkz.secondary_eq}
914: @comment --- 索引用キーワード
915: @findex mt_gkz.secondary_eq
916:
917: @table @t
918: @item mt_gkz.secondary_eq(@var{A},@var{Beta},@var{Ap},@var{Rvec},@var{DirX})
919: :: It returns the secondary equation with respect to cocycles defined by Rvec.
920: @end table
921:
922:
923: @table @var
924: @item return
925: a list of coefficients of the Pfaffian system corresponding to the secondary equation (cf. equation (8) of [MT2020]).
926: @item A,Beta,Ap,Rvec,DirX
927: see @code{pfaff_eq}
928: @end table
929:
930:
931:
932: @comment --- ここで関数の詳しい説明 ---
933: @comment --- @itemize〜@end itemize は箇条書き ---
934: @comment --- @bullet は黒点付き ---
935: @itemize @bullet
936: @item
937: The secondary equation is originally a Pfaffian system for an unkwon @math{r} by @math{r} matrix @math{I} with @math{r=}length(Rvec). We set @math{Y=(I_{11},I_{12},...,I_{1r},I_{21},I_{22},...)^T}. Then, the secondary equation can be seen as a Pfaffian system @math{{dY\over dx_i}=A_iY} with DirX=@math{\{dx_i\}_i}. The function mt_gkz.secondary_eq(@var{A},@var{Beta},@var{Ap},@var{Rvec},@var{DirX}) outputs a list obtained by aligning the matrices @math{A_i}.
938: @item
939: Let @math{F:=(\omega_i)_i} be a column vector whose entries are given by the cohomology classes specified by entries of Rvec. Then, @code{pfaff_eq} computes the Pfaffian matrices @math{P_i} so that @math{{dF\over dx_i}=P_iF}. If @math{Q_i} denotes the matrix obtained by replacing Beta by -Beta, we have @math{A_i=}@code{mt_gkz.kronecker_prd}(E,@math{P_i})+@code{mt_gkz.kronecker_prd}(@math{Q_i},E) where E is the identity matrix of size length(Rvec).
940: @item Options xrule, shift, b_ideal,cg.
941: Same as @code{pfaff_eq}.
942: @end itemize
943:
944: @comment --- @example〜@end example は実行例の表示 ---
945: Example:
946: @example
947: [2647] Beta=[b1,b2,b3]$
948: [2648] DirX=[dx1,dx4]$
949: [2649] Rvec=[[1,0,0,0],[0,0,1,0]]$
950: [2650] A=[[1,1,0,0],[0,0,1,1],[0,1,0,1]]$
951: [2651] Ap=[[1,1,0,0],[0,0,1,1],[0,0,0,0]]$
952: [2652] Xrule=[[x2,1],[x3,1]]$
1.2 takayama 953: [2653] P=mt_gkz.secondary_eq(A,Beta,Ap,Rvec,DirX|xrule=Xrule)$
1.1 takayama 954: --snip--
955: [2654] length(P);
956: 2
957: [2655] P[0];
958: [[(-2*x1^3*x4^2+4*x1^2*x4-2*x1)/(x1^4*x4^2-2*x1^3*x4+x1^2),(b2*x4)/(x1^2*x4-x1),
959: (-b2*x4)/(x1^2*x4-x1),0],[(b1)/(x1*x4-1),
960: ((b2-4/3)*x1^2*x4^2+(-b1-b2+8/3)*x1*x4+b1-4/3)/(x1^3*x4^2-2*x1^2*x4+x1),0,
961: (-b2*x4)/(x1^2*x4-x1)],[(-b1)/(x1*x4-1),0,
962: ((-b2-2/3)*x1^2*x4^2+(b1+b2+4/3)*x1*x4-b1-2/3)/(x1^3*x4^2-2*x1^2*x4+x1),
963: (b2*x4)/(x1^2*x4-x1)],[0,(-b1)/(x1*x4-1),(b1)/(x1*x4-1),0]]
964: <--- Paffian matrix in x1 direction.
965: [2656] P[1];
966: [[0,(b2)/(x1*x4-1),(-b2)/(x1*x4-1),0],[(b1*x1)/(x1*x4^2-x4),
967: ((b2-1/3)*x1^2*x4^2+(-b1-b2+2/3)*x1*x4+b1-1/3)/(x1^2*x4^3-2*x1*x4^2+x4),0,
968: (-b2)/(x1*x4-1)],[(-b1*x1)/(x1*x4^2-x4),0,
969: ((-b2+1/3)*x1^2*x4^2+(b1+b2-2/3)*x1*x4-b1+1/3)/(x1^2*x4^3-2*x1*x4^2+x4),
970: (b2)/(x1*x4-1)],[0,(-b1*x1)/(x1*x4^2-x4),(b1*x1)/(x1*x4^2-x4),0]]
971: <--- Paffian matrix in x4 direction.
972: @end example
973:
974: @comment --- 参照(リンク)を書く ---
975: @table @t
976: @item Refer to
977: @ref{mt_gkz.pfaff_eq}
978: @end table
979: @comment おわり.
980:
981:
982:
983:
984: @node mt_gkz.generate_maple_file_IC,,, Secondary equation
985: @subsection @code{mt_gkz.generate_maple_file_IC}
986: @comment --- 索引用キーワード
987: @findex mt_gkz.generate_maple_file_IC
988:
989: @table @t
990: @item mt_gkz.generate_maple_file_IC(@var{A},@var{Beta},@var{Ap},@var{Rvec},@var{DirX})
991: :: It returns the maple input for a solver of a Pfaffian system IntegrableConnections[RationalSolutions].
992: @end table
993:
994: @comment --- 引数の簡単な説明 ---
995: @table @var
996: @item return
997: a maple input file for the function IntegrableConnections[RationalSolutions] (cf. [BCEW]) for the Pfaffian system mt_gkz.secondary_eq(@var{A},@var{Beta},@var{Ap},@var{Rvec},@var{DirX}).
998: @item A,Beta,Ap,Rvec,DirX
999: see @code{pfaff_eq}.
1000: @end table
1001:
1002: @comment --- ここで関数の詳しい説明 ---
1003: @comment --- @itemize〜@end itemize は箇条書き ---
1004: @comment --- @bullet は黒点付き ---
1005: @itemize @bullet
1006: @item
1007: A maple package IntegrableConnections is available in [BCEW]. In order to use IntegrableConnections, you need to add the global path to the file IntegrableConnections.m to libname on maple. See [BCEW].
1008: @item
1009: If Beta contains unkwon variables, they are regarded as generic parameters. For example, if Beta=[b1,b2,1/5,1/7,b5,...], parameters are [b1,b2,b5,...].
1010: @item Options xrule, shift, b_ideal,cg.
1011: Same as @code{pfaff_eq}.
1012: @item Option filename.
1013: You can specify the file name by specifying the option variable filename. If you do not specify it, @code{generate_maple_file_IC} generates a file "auto-generated-IC.ml".
1014: @end itemize
1015:
1016: @comment --- @example〜@end example は実行例の表示 ---
1017: Example:
1018: @example
1019: [2681] Beta=[b1,b2,1/3]$
1020: [2682] DirX=[dx1,dx4]$
1021: [2683] Rvec=[[1,0,0,0],[0,0,1,0]]$
1022: [2684] A=[[1,1,0,0],[0,0,1,1],[0,1,0,1]]$
1023: [2685] Ap=[[1,1,0,0],[0,0,1,1],[0,0,0,0]]$
1024: [2687] Xrule=[[x2,1],[x3,1]]$
1.2 takayama 1025: [2688] mt_gkz.generate_maple_file_IC(A,Beta,Ap,Rvec,DirX|xrule=Xrule,filename="Test.ml")$
1.1 takayama 1026:
1027:
1028: //A file named Test.ml is automatically generated as follows:
1029:
1030:
1031:
1032: with(OreModules);
1033: with(IntegrableConnections);
1034: with(linalg);
1035: C:=[Matrix([[(-2*x1^3*x4^2+4*x1^2*x4-2*x1)/(x1^4*x4^2-2*x1^3*x4+x1^2),
1036: (b2*x4)/(x1^2*x4-x1),(-b2*x4)/(x1^2*x4-x1),0],[(b1)/(x1*x4-1),
1037: ((b2-4/3)*x1^2*x4^2+(-b1-b2+8/3)*x1*x4+b1-4/3)/(x1^3*x4^2-2*x1^2*x4+x1),0,
1038: (-b2*x4)/(x1^2*x4-x1)],[(-b1)/(x1*x4-1),0,
1039: ((-b2-2/3)*x1^2*x4^2+(b1+b2+4/3)*x1*x4-b1-2/3)/(x1^3*x4^2-2*x1^2*x4+x1),
1040: (b2*x4)/(x1^2*x4-x1)],[0,(-b1)/(x1*x4-1),(b1)/(x1*x4-1),0]]),
1041: Matrix([[0,(b2)/(x1*x4-1),(-b2)/(x1*x4-1),0],[(b1*x1)/(x1*x4^2-x4),
1042: ((b2-1/3)*x1^2*x4^2+(-b1-b2+2/3)*x1*x4+b1-1/3)/(x1^2*x4^3-2*x1*x4^2+x4),0,
1043: (-b2)/(x1*x4-1)],[(-b1*x1)/(x1*x4^2-x4),0,
1044: ((-b2+1/3)*x1^2*x4^2+(b1+b2-2/3)*x1*x4-b1+1/3)/(x1^2*x4^3-2*x1*x4^2+x4),
1045: (b2)/(x1*x4-1)],[0,(-b1*x1)/(x1*x4^2-x4),(b1*x1)/(x1*x4^2-x4),0]])];
1046: RatSols:=RationalSolutions(C,[x1,x4],['param',[b1,b2]]);
1047:
1048:
1049: /*
1050: If you run the output file on maple, you obtain a rational solution of
1051: the secondary equation.
1052: */
1053:
1054: [b2*(3*b1-1)/(b1*x1^2)]
1055: RatSols:=[3*b2/x1 ]
1056: [3*b2/x1 ]
1057: [3*b2-1 ]
1058:
1059: /*
1060: Note that the 4 entries of this vector correspond to entries of a 2 by 2 matrix.
1061: They are aligned as (1,1), (1,2), (2,1) (2,2) from the top.
1062: */
1063: @end example
1064:
1065: @*
1066:
1067: @comment --- 参照(リンク)を書く ---
1068: @table @t
1069: @item Refer to
1070: @ref{mt_gkz.pfaff_eq}
1071: @end table
1072: @comment おわり.
1073:
1074:
1075:
1076:
1077:
1078:
1079:
1080:
1081: @node mt_gkz.generate_maple_file_MR,,, Secondary equation
1082: @subsection @code{mt_gkz.generate_maple_file_MR}
1083: @comment --- 索引用キーワード
1084: @findex mt_gkz.generate_maple_file_MR
1085:
1086: @table @t
1087: @item mt_gkz.generate_maple_file_MR(@var{A},@var{Beta},@var{Ap},@var{Rvec},@var{DirX},@var{D1},@var{D2})
1088: :: It returns the maple input for a solver of a Pfaffian system MorphismsRat[OreMorphisms].
1089: @end table
1090:
1091: @comment --- 引数の簡単な説明 ---
1092: @table @var
1093: @item return
1094: a maple input file for the function MorphismsRat[OreMorphisms] (cf. [CQ]) for the Pfaffian system obtained by @code{secondary_eq}. If you run the output file on maple, you obtain a rational solution of the secondary equation.
1095: @item A,Beta,Ap,Rvec,DirX
1096: see @code{pfaff_eq}.
1097: @item D1,D2
1098: Positive integers. D1 (resp. D2) is the upper bound of the degree of the numerator (resp. denominator) of the solution.
1099: @end table
1100:
1101: @comment --- ここで関数の詳しい説明 ---
1102: @comment --- @itemize〜@end itemize は箇条書き ---
1103: @comment --- @bullet は黒点付き ---
1104: @itemize @bullet
1105: @item
1106: We use the same notation as the explanation of @code{generate_maple_file_IC}. Let @math{D} denote the ring of linear differential operators with coeffiecients in the field of rational functions. We consider @math{D}-modules @math{R:=D^{1\times l}/\sum_{dx_i\in DirX}D^{1\times l}(\partial_i E-P_i)} and @math{S:=D^{1\times l}/\sum_{dx_i\in DirX}D^{1\times l}(\partial_i E+Q_i^T)} where @math{l=}length(Rvec). Then, computing a rational solution of the secondary equation is equivalent to computing a @math{D}-morphism from @math{R} to @math{S} represented by rational function matrix (cf. pp12-13 of [CQ08]).
1107: @item
1108: A maple package OreMorphisms is available in [CQ]. In order to use OreMorphisms, you need to add the global path to the file OreMorphisms.m to libname on maple.
1109: @item Options xrule, shift, b_ideal,cg.
1110: Same as @code{pfaff_eq}.
1111: @item Option filename.
1112: You can specify the file name as in @code{generate_maple_file_IC}.
1113: @item
1114: The difference between @code{generate_maple_file_IC} and @code{generate_maple_file_MR} is the appearence of auxilliary variables D1 and D2. If you can guess the degree of the numerator and the denominator of the solution of the secondary equation, MorphismsRat[OreMorphisms] can be faster than RationalSolutions[IntegrableConnections].
1115: @end itemize
1116:
1117: @comment --- @example〜@end example は実行例の表示 ---
1118: Example:
1119: @example
1120: [2668] Beta=[b1,b2,1/3]$
1121: [2669] DirX=[dx1,dx4]$
1122: [2670] Rvec=[[1,0,0,0],[0,0,1,0]]$
1123: [2671] A=[[1,1,0,0],[0,0,1,1],[0,1,0,1]]$
1124: [2672] Ap=[[1,1,0,0],[0,0,1,1],[0,0,0,0]]$
1125: [2673] Xvar=[x1,x4]$
1126: [2674] Xrule=[[x2,1],[x3,1]]$
1.2 takayama 1127: [2675] mt_gkz.generate_maple_file_MR(A,Beta,Ap,Rvec,DirX,2,2|xrule=Xrule)$
1.1 takayama 1128:
1129:
1130: //A file "auto-generated-MR.ml" is automatically generated as follows:
1131:
1132:
1133: with(OreModules);
1134: with(OreMorphisms);
1135: with(linalg);
1136: Alg:=DefineOreAlgebra(diff=[dx1,x1],diff=[dx4,x4],polynom=[x1,x4],comm=[b1,b2]);
1137: P:=Matrix([[dx1,0],[0,dx1],[dx4,0],[0,dx4]])
1138: -Matrix([[((b1+b2-4/3)*x1*x4-b1+4/3)/(x1^2*x4-x1),(-b2*x4)/(x1^2*x4-x1)],
1139: [(-b1)/(x1*x4-1),(b1*x4)/(x1*x4-1)],[(b2*x1)/(x1*x4-1),(-b2)/(x1*x4-1)],
1140: [(-b1*x1)/(x1*x4^2-x4),(1/3*x1*x4+b1-1/3)/(x1*x4^2-x4)]]);
1141: Q:=Matrix([[dx1,0],[0,dx1],[dx4,0],[0,dx4]])
1142: +Matrix([[((-b1-b2-2/3)*x1*x4+b1+2/3)/(x1^2*x4-x1),(b1)/(x1*x4-1)],
1143: [(b2*x4)/(x1^2*x4-x1),(-b1*x4)/(x1*x4-1)],[(-b2*x1)/(x1*x4-1),(b1*x1)/(x1*x4^2-x4)],
1144: [(b2)/(x1*x4-1),(-1/3*x1*x4-b1+1/3)/(x1*x4^2-x4)]]);
1145: RatSols:=MorphismsRat(P,Q,Alg,0,2,2);
1146:
1147: /*
1148: If you run the output file on maple, you obtain a vector RatSols.
1149: RatSols[1] is the rational solution of the secondary equation:
1150: */
1151:
1152: RatSols[1]:=[(1/3)*@math{n_{2_{1_{3_1}}}}*(3*b1-1)/(b1*x1^2*@math{d_{6_1}}) @math{n_{2_{1_{3_1}}}}/(x1*@math{d_{6_1}})]
1153: [@math{n_{2_{1_{3_1}}}}/(x1*@math{d_{6_1}}) (1/3)*@math{n_{2_{1_{3_1}}}}*(3*b2-1)/(b2*@math{d_{6_1}})]
1154:
1155: /*
1156: Here, @math{n_{2_{1_{3_1}}}} and @math{d_{6_1}} are arbitrary constants. We can take @math{n_{2_{1_{3_1}}}=3*b2} and @math{d_{6_1}=1} to obtain the rational solution of the secondary equation which is identical to the one obtained from @code{generate_maple_file_IC}.
1157: */
1158: @end example
1159:
1160: @*
1161:
1162: @comment --- 参照(リンク)を書く ---
1163: @table @t
1164: @item Refer to
1165: @ref{mt_gkz.pfaff_eq}, @ref{mt_gkz.generate_maple_file_IC}.
1166: @end table
1167: @comment おわり.
1168:
1169:
1170:
1171:
1172:
1173:
1174:
1175:
1176:
1177:
1178:
1179:
1180: @node Normalizing constant,,, Cohomology intersection numbers
1181: @section Normalizing the cohomology intersection matrix
1182:
1183:
1184: @node mt_gkz.principal_normalizing_constant,,, Normalizing constant
1185: @subsection @code{mt_gkz.principal_normalizing_constant}
1186: @comment --- 索引用キーワード
1187: @findex mt_gkz.principal_normalizing_constant
1188:
1189: @table @t
1190: @item mt_gkz.principal_normalizing_constant(@var{A},@var{T},@var{Beta},@var{K})
1191: :: It returns the normalizing constant of the cohomology intersection matrix in terms of a regular triangulation T.
1192: @end table
1193:
1194: @comment --- 引数の簡単な説明 ---
1195: @table @var
1196: @item return
1.3 ! takayama 1197: a rational function which is the cohomology intersection number @math{{1\over (2\pi\sqrt{-1})^n} \langle[{dt\over t}],[{dt\over t}]\rangle_{ch}} in terms of the regular triangulation T. Here, @math{n} is the number of integration variables and @math{dt\over t} is the volume form @math{{dt_1\over t_1}\wedge\cdots\wedge{dt_n\over t_n}} of the complex @math{n}-torus.
1.1 takayama 1198: @item A,Beta
1199: see @code{pfaff_eq}.
1200: @item T
1201: a regular triangulation of A.
1202: @item K
1203: The number of polynomial factors in the integrand. see [MT2020].
1204: @end table
1205:
1206: @comment --- ここで関数の詳しい説明 ---
1207: @comment --- @itemize〜@end itemize は箇条書き ---
1208: @comment --- @bullet は黒点付き ---
1209: @itemize @bullet
1210: @item
1.3 ! takayama 1211: This function is useful when the basis of the cohomology group @math{\{\omega_i\}_{i=1}^r} is given so that @math{\omega_1=[{dt\over t}]}.
1.1 takayama 1212: @item
1.3 ! takayama 1213: One can find a regular triangulation by using a function @code{mt_gkz.regular_triangulation}.
! 1214: @item
! 1215: @code{mt_gkz.leading_terms} can be used more generally.
1.1 takayama 1216: @end itemize
1217:
1218: @comment --- @example〜@end example は実行例の表示 ---
1219: Example:
1220: @example
1221: [2676] A=[[1,1,0,0],[0,0,1,1],[0,1,0,1]]$
1222: [2677] Beta=[b1,b2,b3]$
1223: [2678] K=2$
1224: [2679] T=[[1,2,3],[2,3,4]]$
1.2 takayama 1225: [2680] mt_gkz.principal_normalizing_constant(A,T,Beta,K);
1.1 takayama 1226: (-b1-b2)/(b3*b1+b3*b2-b3^2)
1227: @end example
1228:
1229: @comment --- 参照(リンク)を書く ---
1230: @table @t
1231: @item Refer to
1.3 ! takayama 1232: @ref{mt_gkz.leading_terms}.
1.1 takayama 1233: @end table
1234: @comment おわり.
1235:
1236:
1237:
1238:
1239:
1240:
1241:
1242:
1.3 ! takayama 1243: @node mt_gkz.leading_terms,,, Normalizing constant
! 1244: @subsection @code{mt_gkz.leading_terms}
1.1 takayama 1245: @comment --- 索引用キーワード
1246: @findex mt_gkz.leading_terms
1247:
1248: @table @t
1.3 ! takayama 1249: @item mt_gkz.leading_terms(@var{A},@var{Beta},@var{W},@var{Q1},@var{Q2},@var{K},@var{N})
1.1 takayama 1250: :: It returns the W-leading terms of a cohomology intersection number specified by Q1 and Q2 up to W-degree=(minimum W-degree)+N.
1251: @end table
1252:
1253: @comment --- 引数の簡単な説明 ---
1254: @table @var
1255: @item return
1.3 ! takayama 1256: a list [[C1,DEG1],[C2,DEG2],...]. Each CI is a rational function depending on Beta times a monomial @math{x^m} in x-variables. DEGI is the W-degree of @math{x^m}. The cohomology intersection number @math{{1\over (2\pi\sqrt{-1})^n} \langle[h^{-q_1^\prime}t^{q_1^{\prime\prime}}{dt\over t}],[h^{-q_2^\prime}t^{q_2^{\prime\prime}}{dt\over t}]\rangle_{ch}} has a Laurent expansion of the form C1+C2+....
1.1 takayama 1257: @item A,Beta
1258: see @code{pfaff_eq}.
1259: @item W
1260: a positive and integral weight vector.
1261: @item Q1,Q2
1262: @math{Q1=(q_1^\prime,q_1^{\prime\prime})^T}, @math{Q2=(q_2^\prime,q_2^{\prime\prime})^T} are integer vectors. The lengths of @math{q_1^\prime} and @math{q_2^\prime} are both equal to @math{K}.
1263: @item K
1264: The number of polynomial factors in the integrand. see [MT2020].
1265: @item N
1266: A positive integer.
1267: @end table
1268:
1269: @comment --- ここで関数の詳しい説明 ---
1270: @comment --- @itemize〜@end itemize は箇条書き ---
1271: @comment --- @bullet は黒点付き ---
1272: @itemize @bullet
1273: @item
1274: For a monomial @math{x^m=x_1^{m_1}\cdots x_n^{m_n}} and a weight vector @math{W=(w_1,\dots,w_n)}, the W-degree of @math{x^m} is given by the dot product @math{m\cdot W=m_1w_1+\cdots +m_nw_n}.
1275: @item
1.3 ! takayama 1276: The W-leading terms of the cohomology intersection number @math{{1\over (2\pi\sqrt{-1})^n} \langle[h^{-q_1^\prime}t^{q_1^{\prime\prime}}{dt\over t}],[h^{-q_2^\prime}t^{q_2^{\prime\prime}}{dt\over t}]\rangle_{ch}} can be computed by means of Theorem 2.6 of [GM2020]. See also Theorem 3.4.2 of [SST2000].
1.1 takayama 1277: @item
1278: If the weight vector is not generic, you will receive an error message such as "WARNING(initial_mon): The weight may not be generic". In this case, the output may be wrong and you should retake a suitable W. To be more precise, W should be chosen from an open cone of the Groebner fan.
1279: @item Option xrule.
1280: Same as @code{pfaff_eq}.
1281: @end itemize
1282:
1283: @comment --- @example〜@end example は実行例の表示 ---
1284: Example:
1285: @example
1286: [2922] Beta=[b1,b2,1/3];
1287: [b1,b2,1/3]
1288: [2923] Q=[[1,0,0],[0,1,0]];
1289: [[1,0,0],[0,1,0]]
1290: [2924] A=[[1,1,0,0],[0,0,1,1],[0,1,0,1]];
1291: [[1,1,0,0],[0,0,1,1],[0,1,0,1]]
1292: [2925] W=[1,0,0,0];
1293: [1,0,0,0]
1294: [2926] K=2;
1295: 2
1296: [2927] N=2;
1297: 2
1.3 ! takayama 1298: [2928] NC=mt_gkz.leading_terms(A,Beta,W,Q[0],Q[1],K,N|xrule=[[x2,1],[x3,1],[x4,1]])$
1.1 takayama 1299: --snip--
1300: [2929] NC;
1301: [[(-3)/(x1),-5],[0,-4],[0,-3]]
1302:
1303:
1304: /*
1305: This output means that the W-leading term of the (1,2) entry of the cohomology
1306: intersection matrix is @math{(-3)/(x1)\times (2\pi\sqrt{-1})}. In view of examples of @code{generate_maple_file_IC} or @code{generate_maple_file_MR}, we can conclude that the cohomology
1307: intersection matrix is given by
1308: */
1309:
1310: [-(3*b1-1)/(b1*x1^2) -3/x1 ]
1311: [-3/x1 -(3*b2-1)/b2]]
1312:
1313:
1314: //divided by 2@math{\pi\sqrt{-1}}.
1315: @end example
1316:
1317:
1318: @comment --- 参照(リンク)を書く ---
1319: @table @t
1320: @item Refer to
1.3 ! takayama 1321: @ref{mt_gkz.leading_terms}, @ref{mt_gkz.generate_maple_file_IC}, @ref{mt_gkz.generate_maple_file_MR}.
1.1 takayama 1322: @end table
1323: @comment おわり.
1324:
1325:
1326:
1327:
1328:
1329: @node mt_gkz.leading_term_rat,,, Normalizing constant
1330: @subsection @code{mt_gkz.leading_term_rat}
1331: @comment --- 索引用キーワード
1332: @findex mt_gkz.leading_term_rat
1333:
1334: @table @t
1335: @item mt_gkz.leading_term_rat(@var{P},@var{W},@var{V})
1336: :: It returns the W-leading term of a rational function P depending on variables V.
1337: @end table
1338:
1339: @comment --- 引数の簡単な説明 ---
1340: @table @var
1341: @item return
1342: It returns the W-leading term of a rational function P.
1343: @item P
1344: a rational function.
1345: @item W
1346: a weight vector.
1347: @item V
1348: a list of variables of P.
1349: @end table
1350:
1351: @comment --- ここで関数の詳しい説明 ---
1352: @comment --- @itemize〜@end itemize は箇条書き ---
1353: @comment --- @bullet は黒点付き ---
1354: @itemize @bullet
1355: @item
1.3 ! takayama 1356: This function is supposed to be combined with @code{leading_terms} to compute the leading term of a cohomology intersection number.
1.1 takayama 1357: @item
1358: If W is chose so that there are several initial terms, you will receive an error message "WARNING(leading_term_rat):The weight vector may not be generic."
1359: @end itemize
1360:
1361:
1362: @comment --- 参照(リンク)を書く ---
1363: @table @t
1364: @item Refer to
1.3 ! takayama 1365: @ref{mt_gkz.leading_terms}.
1.1 takayama 1366: @end table
1367: @comment おわり.
1368:
1369:
1370:
1371:
1372:
1373:
1374: @node Regular triangulations,,, Cohomology intersection numbers
1375: @section Regular triangulations
1376:
1377: @comment --- 個々の関数の説明 ---
1378: @comment --- section 名を正確に ---
1379: @node mt_gkz.toric_gen_initial,,, Regular triangulations
1380: @node mt_gkz.regular_triangulation,,, Regular triangulations
1381: @node mt_gkz.top_standard_pairs,,, Regular triangulations
1382: @subsection @code{mt_gkz.toric_gen_initial}, @code{mt_gkz.regular_triangulation}, @code{mt_gkz.top_standard_pairs}
1383: @comment --- 索引用キーワード
1384: @findex mt_gkz.toric_gen_initial
1385: @findex mt_gkz.regular_triangulation
1386: @findex mt_gkz.top_standard_pairs
1387:
1388: @table @t
1389: @item mt_gkz.toric_gen_initial(@var{A},@var{W})
1390: @item mt_gkz.regular_triangulation(@var{A},@var{W})
1391: @item mt_gkz.top_standard_pairs(@var{A},@var{W})
1392: :: utility functions for computing ring theoretic invariants: generic initial ideal for the toric ideal specified by the matrix A and a weight W, its associated regular triangulation, and its associated top-dimensional standard pairs.
1393: @end table
1394:
1395: @comment --- 引数の簡単な説明 ---
1396: @table @var
1397: @item return
1398: @code{toric_gen_initial} returns a list [L1,L2] of length 2. L1 is a list of generators of the W-initial ideal of the toric ideal @math{I_A} specified by A. L2 is a list of variables of @math{I_A}.
1399: @item return
1400: @code{regular_triangulation} returns a list of simplices of a regular triangulation @math{T_W} specified by the weight W.
1401: @item return
1402: @code{top_standard_pairs} returns a list of the form [[L1,S1],[L2,S2],...]. Each SI is a simplex of @math{T_W}. Each LI is a list of exponents.
1403: @item A
1404: a configuration matrix.
1405: @item W
1406: a positive weight vector.
1407: @end table
1408:
1409: @comment --- ここで関数の詳しい説明 ---
1410: @comment --- @itemize〜@end itemize は箇条書き ---
1411: @comment --- @bullet は黒点付き ---
1412: @itemize @bullet
1413: @item
1414: As for the definition of the standard pair, see Chapter 3 of [SST00].
1415: @item
1416: We set n=length(A) and set BS1:=@math{\{ 1,2,...,n\}\setminus S1}. Then, each L1[I] is an exponent @math{\bf k} of a top-dimensional standard pair @math{(\partial^{\bf k}_{BS1},S1)}. Here, @math{\bf k} is a list of length n-length(S1) and @math{\partial_{BS1}=(\partial_J)_{J\in BS1}}.
1417: @item
1.3 ! takayama 1418: If the weight vector is not generic, you will receive an error message such as "WARNING(initial_mon): The weight may not be generic". See also @code{leading_terms}.
1.1 takayama 1419: @item
1.3 ! takayama 1420: These functions are utilized in @code{leading_terms}.
1.1 takayama 1421: @end itemize
1422:
1423: @comment --- @example〜@end example は実行例の表示 ---
1424: Example: An example of a non-unimodular triangulation and non-trivial standard pairs.
1425: @example
1426: [3256] A=[[1,1,1,1,1],[0,1,0,2,0],[0,0,1,0,2]];
1427: [[1,1,1,1,1],[0,1,0,2,0],[0,0,1,0,2]]
1428: [3257] W=[2,0,1,2,2];
1429: [2,0,1,2,2]
1.3 ! takayama 1430: [3258] mt_gkz.toric_gen_initial(A,W);
1.1 takayama 1431: --snip--
1432: [[x1*x5,x1*x4,x3^2*x4],[x1,x2,x3,x4,x5]]
1.3 ! takayama 1433: [3259] mt_gkz.regular_triangulation(A,W);
1.1 takayama 1434: --snip--
1435: [[2,4,5],[2,3,5],[1,2,3]]
1.3 ! takayama 1436: [3260] mt_gkz.top_standard_pairs(A,W);
1.1 takayama 1437: --snip--
1438: [[[[0,0],[0,1]],[2,4,5]],[[[0,0]],[2,3,5]],[[[0,0]],[1,2,3]]]
1439:
1440: /*
1441: This means that the regular triangulation of the configuration matrix A is
1442: given by @math{T=\{\{2,4,5\},\{2,3,5\},\{1,2,3\}\}}. The normalized volumes of these simplices
1443: are 2,1 and 1. Moreover, the top-dimensional standard pairs are
1444: @math{(1,\{2,4,5\}),(\partial_3,\{2,4,5\})}, @math{(1,\{2,3,5\})},@math{(1,\{1,2,3\})}.
1445: */
1446: @end example
1447:
1448:
1449:
1450: @comment --- 参照(リンク)を書く ---
1451: @table @t
1452: @item Refer to
1.3 ! takayama 1453: @ref{mt_gkz.leading_terms}.
1.1 takayama 1454: @end table
1455: @comment おわり.
1456:
1457:
1458:
1459:
1460:
1461:
1462:
1463: @comment --- おまじない ---
1464: @node Index,,, Top
1465: @unnumbered Index
1466: @printindex fn
1467: @printindex cp
1468: @iftex
1469: @vfill @eject
1470: @end iftex
1471: @summarycontents
1472: @contents
1473: @bye
1474: @comment --- おまじない終り ---
1475:
1476: @comment *********************************************************
1477: @comment ********* template
1478: @comment **********************************************************
1479: @comment --- 個々の関数の説明 ---
1480: @comment --- section 名を正確に ---
1481: @node mt_gkz.pfaff_eq,,, Pfaff equation for given cocycles
1482: @subsection @code{mt_gkz.pfaff_eq}
1483: @comment --- 索引用キーワード
1484: @findex mt_gkz.pfaff_eq
1485:
1486: @table @t
1487: @item mt_gkz.pfaff_eq(@var{A},@var{Beta},@var{Ap},@var{Rvec},@var{DirX})
1488: :: It returns the Pfaff equation for the GKZ system defined by @var{A} and @var{Beta} with respect to cocycles defined by @var{Rvec}.
1489: @end table
1490:
1491: @comment --- 引数の簡単な説明 ---
1492: @table @var
1493: @item return
1494: a list of coefficients of the Pfaff equation with respect to the direction @var{DirX}
1495: @item A
1496: the matrix A of the GKZ system.
1497: @item Beta
1498: ...
1499: @end table
1500:
1501: @comment --- ここで関数の詳しい説明 ---
1502: @comment --- @itemize〜@end itemize は箇条書き ---
1503: @comment --- @bullet は黒点付き ---
1504: @itemize @bullet
1505: @item
1506: The independent variables are @code{x1,x2,x3,...} (@math{x_1, x_2, x_3, \ldots}).
1507: @end itemize
1508:
1509: @comment --- @example〜@end example は実行例の表示 ---
1510: Example: Gauss hypergeometric system, see [GM2020] example ??.
1511: @example
1512: [1883] import("mt_gkz.rr");
1513: @end example
1514:
1515: @comment --- 参照(リンク)を書く ---
1516: @table @t
1517: @item Refer to
1518: @ref{mt_gkz.pfaff_eq}
1519: @end table
1520: @comment おわり.
FreeBSD-CVSweb <freebsd-cvsweb@FreeBSD.org>