API Documentation

euler_product.lattice_invariant_euler_products

The main function of this package is get_euler_products which computes with interval arithmetic and a proven precision Euler products of rational functions over primes in special sets modulo some fixed q. These special sets are the lattice invariant classes modulo q, and the software also enables the user to use them through the class ComponentStructure.

AUTHORS:

  • Olivier Ramaré (2023-01-008) : initial version

  • Dominique Benielli (2023-02_15) Aix Marseille Université , Integration as SageMath package. Cellule de developpement Institut Archimède

…WARNING:

Needs Sage version at least 9.0 CAREFUL, this is Python 3 code!

EXAMPLES:

sage: from euler_product.lattice_invariant_euler_products import get_euler_products
euler_product.lattice_invariant_euler_products.get_euler_products(q, s, f_init, h_init, nb_decimals=100, big_p=300, verbose=2, with_laTeX=0, digital_offset=10)[source]

Returns the pair ((A), (approx_prod_(p in A mod q) f_init(1/p^s) / h_init(1/p^s) ) ) where (A) is the tuple of the lattice-invariant classes modulo q and approx_prod_(p in A mod q) f_init(1/p^s) / h_init(1/ps) ) is an arithmetic interval approximation of the product over every prime in the class A modulo q of the quotient f_init(1/p^s) / h_init(1/p^s) given in the form of a pair (lower_bound, upper_bound). We expect the difference upper_bound - lower bound to be < 10^(-nb_decimals) but this is not guaranteed. In case it does not happen, increase nb_decimals slightly. We ask at the beginning for digital_offset more (binary) digits. We compute directly what happens for primes < big_p. We assume that f_init(0) = h_init(0) = 1, that s is a positive real number and that \(\Delta s > 1\) where \(\Delta\) is the order of the zero of f_init-h_init at 0. This last condition is to ensure the Euler products converge absolutely. See Theorem 2 of the reference file.

to do

assert F[0] = H[0] = 1

INPUT:

  • q – int

    a positive integer. The products are taken over classes modulo q.

  • s – int, rat or real number

    A real number > 0. It should be given with enough precision to enable the computations, so either an exact type or a RealIntervalField(...) number, given with enough precision. As this precision is given in binary digits, using 10*nb_decimals is a safe choice. Notice that, if you want to have s = 2.1, better use 21/10. Additional conditions may be required for the Euler products to be absolutely convergent.

  • f_init – pol

    a polynomial with real coefficients and such that f_init(0) = 1.

  • h_init – pol

    a polynomial with real coefficients and such that h_init(0) = 1.

  • nb_decimals – int (default: 100), optional

    The number of decimals that are being sought by the final result. The function aims at such a number of decimals but a final tuning may be required.

  • big_p – int (default:300), optional

    This is an internal parameter that is described in the accompanying paper. In short: the Euler products up to big_p are computed directly.

  • verbose – int (default: 2), optional

    Defines the amount of output shown. It may take the usual values 0, 1, 2, towards more explanations. When get_vs is used inside another function, verbose == 0 is usually what is required. The value -1 is special and the effect is fully described in the tutorial.

  • with_laTeX – int (default: 0), optional

    This parameter takes the value either 1 or not 1. As of now, this has effect only when verbose == 2.

  • digits_offset – int (default: 10), optional

    Not used yet.

OUTPUT:

pair of tuples

The output is a pair whose first component is the tuple of lattice invariant classes (A) and second component is the corresponding tuple of values (prod_(p in A mod q) f_init(1/p^s) / h_init(1/p^s) ) where each value is given in interval arithmetic as a pair (lower_bound, upper_bound).

EXCEPTIONS:

ValueError (‘non convergent product’) ValueError(“f_init[0] and h_init[0] must be equal to 1”)

EXAMPLES:

sage: from euler_product.lattice_invariant_euler_products import get_euler_products
sage: get_euler_products(7, 21/10, 1-x^3, 1+2*x^2, 100, 100, 0)  # doctest: +NORMALIZE_WHITESPACE
((frozenset({1}), frozenset({6}), frozenset({2, 4}), frozenset({3, 5})),
 ((0.9999982391236771174582758043183901338942364901235699217522601062931335918060239723453736409102740196458132617578911976337827035056548487,
   0.9999982391236771174582758043183901338942364901235699217522601062931335918060239723453736409102740196458132617578911976337827035058702859),
  (0.9999576136884417398077559625848130088885656351740787265112227071217155682725032721589661739481265973172546756861113391191295834691038278,
   0.9999576136884417398077559625848130088885656351740787265112227071217155682725032721589661739481265973172546756861113391191295834695309445),
  (0.8903351065070010591619870364916093462000320541037928008286414361647911118617149004528444428927243238343453800105285278416937429697527759,
   0.8903351065070010591619870364916093462000320541037928008286414361647911118617149004528444428927243238343453800105285278416937429701294787),
  (0.9772686478893137854388184266844545895906115657758499208289733302484239589826603294718981918722254050003289550536985865206208817481509527,
   0.9772686478893137854388184266844545895906115657758499208289733302484239589826603294718981918722254050003289550536985865206208817489644518)))

sage: from euler_product.lattice_invariant_euler_products import get_euler_products
sage: from sage.all import RealNumber
sage: ss = RealIntervalField(1000)(2.1)
sage: get_euler_products(7, ss, 1-x^3, 1+2*x^2, 100, 100, 0)  # doctest: +NORMALIZE_WHITESPACE
((frozenset({1}), frozenset({6}), frozenset({2, 4}), frozenset({3, 5})),
 ((0.9999982391236771174593563029845165888949925030802468731879907340376417409448258804977425145432276967368069400485351556253529538963227206,
   0.9999982391236771174593563029845165888949925030802468731879907340376417409448258804977425145432276967368069400485351556253529538964531787),
 (0.9999576136884417398271690198938580248373051070700165881172968559533702467774954223949082638318313973207279942499461484456197967852358670,
  0.9999576136884417398271690198938580248373051070700165881172968559533702467774954223949082638318313973207279942499461484456197967854939739),
 (0.8903351065070010720688279359417577943450315878955017449322206666706753000624035653585286591685046103123298899332142094572919914905004413,
  0.8903351065070010720688279359417577943450315878955017449322206666706753000624035653585286591685046103123298899332142094572919914907258341),
 (0.9772686478893137901030489977249098644207078284256772977807607160813875957724686047692999490530968236161711793835695795600577094636101003,
  0.9772686478893137901030489977249098644207078284256772977807607160813875957724686047692999490530968236161711793835695795600577094640930035)))
euler_product.lattice_invariant_euler_products.get_vs(q, s, nb_decimals=100, big_p=100, verbose=2, with_laTeX=0, digits_offset=10)[source]

Returns the pair ((A), (approx_zeta(s; q, A))) where (A) is the tuple of the lattice-invariant classes modulo q and approx_zeta(s; q, A) is an arithmetic interval approximation of \(\zeta(s; q, A) = \prod_{p\in A}(1-p^{-s})^{-1}\) given in the form of a pair (lower_bound, upper_bound).

We expect the difference upper_bound - lower bound to be < 10^(-nb_decimals) but this is not guaranteed. In case it does not happen, increase nb_decimals slightly. We compute directly what happens for primes < big_p. We ask at the beginning for digits_offset more (binary) digits.

INPUT:

  • q – int

    The products are taken over classes modulo q.

  • s – int, rat or real number

    A real number > 1. It should be given with enough precision to enable the computations, so either an exact type or a RealIntervalField(...) number, given with enough precision. As this precision is given in binary digits, using 10*nb_decimals is a safe choice. Notice that, if you want to have s = 2.1, better use 21/10.

  • nb_decimals – int (default: 100)

    The number of decimals that are being sought by the final result. The function aims at such a number of decimals but a final tuning may be required.

  • big_p – int (default: 100), optional

    This is an internal parameter that is described in the accompanying paper. In short: the Euler products up to big_p are computed directly.

  • verbose – int (default: 2), optional

    Defines the amount of output shown. It may take the usual values 0, 1, 2, towards more explanations. When get_vs is used inside another function, verbose = 0 is usually what is required. The value -1 is special and the effect is fully described in the tutorial.

  • with_laTeX – int (default: 0), optional

    This parameter takes the value 1 or not 1. As of now, this has effect only when verbose == 2.

  • digits_offset – int (default: 10), optional

    We ask for some more digits, see above.

OUTPUT:

pair of tuples

The output is a pair whose first component is the tuple of lattice invariant classes (A) and second component is the corresponding tuple of values \((\zeta(s; q, A))\) where each value is given in interval arithmetic as a pair (lower_bound, upper_bound).

EXAMPLES:

sage: from euler_product.lattice_invariant_euler_products import get_vs
sage: from sage.all import RealNumber
sage: get_vs(8, 3, 100) # doctest: +NORMALIZE_WHITESPACE
Computing the structural invariants ...  done.
Computing big m ... Computing the finite product for p < 100 ...  done.
done: we use big_m = 18 .
Building indices ... done: there are 5 summands.
-------------------
For p + 8ZZ in frozenset({1})
the product of 1 / (1 - p^{-3}) is between
1.00022487189858708836232213399171649391737471516970709876892216031894460446108615250640526399629122151838389
and
1.00022487189858708836232213399171649391737471516970709876892216031894460446108615250640526399629122151838407
(Obtained:  104  correct decimal digits)
-------------------
For p + 8ZZ in frozenset({3})
the product of 1 / (1 - p^{-3}) is between
1.03941995442465269726466028414808844655561938824520417669418677265825033928903395095004198994772110633052081
and
1.03941995442465269726466028414808844655561938824520417669418677265825033928903395095004198994772110633052096
(Obtained:  105  correct decimal digits)
-------------------
For p + 8ZZ in frozenset({5})
the product of 1 / (1 - p^{-3}) is between
1.00859929667035262471282393658930645974303187198527123038915644169227273758988775728257540659401768223811113
and
1.00859929667035262471282393658930645974303187198527123038915644169227273758988775728257540659401768223811127
(Obtained:  105  correct decimal digits)
-------------------
For p + 8ZZ in frozenset({7})
the product of 1 / (1 - p^{-3}) is between
1.00305724526111078841419961903241251128776224554544642576504934327705380373558762279204676597516287864231117
and
1.00305724526111078841419961903241251128776224554544642576504934327705380373558762279204676597516287864231131
(Obtained:  105  correct decimal digits)
((frozenset({1}), frozenset({3}), frozenset({5}), frozenset({7})),
 ((1.00022487189858708836232213399171649391737471516970709876892216031894460446108615250640526399629122151838389,
   1.00022487189858708836232213399171649391737471516970709876892216031894460446108615250640526399629122151838407),
  (1.03941995442465269726466028414808844655561938824520417669418677265825033928903395095004198994772110633052081,
   1.03941995442465269726466028414808844655561938824520417669418677265825033928903395095004198994772110633052096),
  (1.00859929667035262471282393658930645974303187198527123038915644169227273758988775728257540659401768223811113,
   1.00859929667035262471282393658930645974303187198527123038915644169227273758988775728257540659401768223811127),
  (1.00305724526111078841419961903241251128776224554544642576504934327705380373558762279204676597516287864231117,
   1.00305724526111078841419961903241251128776224554544642576504934327705380373558762279204676597516287864231131)))

sage: from euler_product.lattice_invariant_euler_products import get_vs
sage: from sage.all import RealNumber
sage: ss = RealIntervalField(1000)(2.1)
sage: get_vs(7, ss, 100) # doctest: +NORMALIZE_WHITESPACE
Computing the structural invariants ...  done.
Computing big m ... Computing the finite product for p < 100 ...  done.
done: we use big_m = 25 .
Building indices ... done: there are 11 summands.
-------------------
For p + 7ZZ in frozenset({1})
the product of 1 / (1 - p^{-2.10000000000000008881784197001252323389053344726562500000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000?}) is between
1.0015251649887938725660913688010517101666208733880109315688816926296884362067543474803469725091159142720127867
and
1.0015251649887938725660913688010517101666208733880109315688816926296884362067543474803469725091159142721524294
(Obtained:  102  correct decimal digits)
-------------------
For p + 7ZZ in frozenset({6})
the product of 1 / (1 - p^{-2.10000000000000008881784197001252323389053344726562500000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000?}) is between
1.0053143647905533679330453141809294714882943247539536696871604072988921328496577468083535690636615857899394878
and
1.0053143647905533679330453141809294714882943247539536696871604072988921328496577468083535690636615857900796593
(Obtained:  100  correct decimal digits)
-------------------
For p + 7ZZ in frozenset({2, 4})
the product of 1 / (1 - p^{-2.10000000000000008881784197001252323389053344726562500000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000?}) is between
1.3163847262351936805824813658507662946352860144404616097232556176854606556798278964523547342562974874324307818
and
1.3163847262351936805824813658507662946352860144404616097232556176854606556798278964523547342562974874326143261
(Obtained:  102  correct decimal digits)
-------------------
For p + 7ZZ in frozenset({3, 5})
the product of 1 / (1 - p^{-2.10000000000000008881784197001252323389053344726562500000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000000?}) is between
1.1573918393315763316569087551275677116540398269978595705035335829359240632731578772727923341501394332932502825
and
1.1573918393315763316569087551275677116540398269978595705035335829359240632731578772727923341501394332934116590
(Obtained:  102  correct decimal digits)
((frozenset({1}), frozenset({6}), frozenset({2, 4}), frozenset({3, 5})),
 ((1.0015251649887938725660913688010517101666208733880109315688816926296884362067543474803469725091159142720127867,
   1.0015251649887938725660913688010517101666208733880109315688816926296884362067543474803469725091159142721524294),
  (1.0053143647905533679330453141809294714882943247539536696871604072988921328496577468083535690636615857899394878,
   1.0053143647905533679330453141809294714882943247539536696871604072988921328496577468083535690636615857900796593),
  (1.3163847262351936805824813658507662946352860144404616097232556176854606556798278964523547342562974874324307818,
   1.3163847262351936805824813658507662946352860144404616097232556176854606556798278964523547342562974874326143261),
  (1.1573918393315763316569087551275677116540398269978595705035335829359240632731578772727923341501394332932502825,
   1.1573918393315763316569087551275677116540398269978595705035335829359240632731578772727923341501394332934116590)))

TESTS:

sage: from euler_product.lattice_invariant_euler_products import get_vs
sage: from sage.all import RealNumber
sage: get_vs(3, 2, 100)  # doctest: +NORMALIZE_WHITESPACE
Computing the structural invariants ...  done.
Computing big m ... Computing the finite product for p < 100 ...  done.
done: we use big_m = 26 .
Building indices ... done: there are 5 summands.
-------------------
For p + 3ZZ in frozenset({1})
the product of 1 / (1 - p^{-2}) is between
1.0340148754143418805390306444130476285789654284890998864168250384212222458710963580496217079826205962897974283
and
1.0340148754143418805390306444130476285789654284890998864168250384212222458710963580496217079826205962901601292
(Obtained:  100  correct decimal digits)
-------------------
For p + 3ZZ in frozenset({2})
the product of 1 / (1 - p^{-2}) is between
1.4140643908921476375655018190798293799076950693931621750399249624239281069920884994537548585024751141999583734
and
1.4140643908921476375655018190798293799076950693931621750399249624239281069920884994537548585024751142004543841
(Obtained:  99  correct decimal digits)
((frozenset({1}), frozenset({2})),
 ((1.0340148754143418805390306444130476285789654284890998864168250384212222458710963580496217079826205962897974283,
   1.0340148754143418805390306444130476285789654284890998864168250384212222458710963580496217079826205962901601292),
  (1.4140643908921476375655018190798293799076950693931621750399249624239281069920884994537548585024751141999583734,
   1.4140643908921476375655018190798293799076950693931621750399249624239281069920884994537548585024751142004543841)))
euler_product.lattice_invariant_euler_products.get_vs_checker(q, s, borne=10000)[source]

This is a low level sanity check engine described in the tutorial. It is to be used by developers only.

INPUT:

  • q – int

    The products are taken over lattice invariant classes modulo q.

  • s – real

    A real number > 1.

  • borne – int (default: 10000), optional

    boundary of computation.

EXAMPLES:

sage: from euler_product.lattice_invariant_euler_products import get_vs_checker
sage: get_vs_checker(8, 2)
-------------------
For p mod  8  in  frozenset({1})
the product of 1/(1-p^{- 2 }) is about 1.0048326237351608
-------------------
For p mod  8  in  frozenset({3})
the product of 1/(1-p^{- 2 }) is about 1.1394159722583108
-------------------
For p mod  8  in  frozenset({5})
the product of 1/(1-p^{- 2 }) is about 1.0510974216618003
-------------------
 For p mod  8  in  frozenset({7})
 the product of 1/(1-p^{- 2 }) is about 1.0251478255836493
euler_product.lattice_invariant_euler_products.table_performance(min_q, max_q, nb_decimals=100, big_p=300)[source]

The behaviour of this function is described in the attached tutorial.

INPUT:

  • min_q – int

    The modulus q goes through all the values in [min_q, max_q] that are not twice an odd integer.

  • max_q – int

    The modulus q goes through all the values in [min_q, max_q] that are not twice an odd integer.

  • nb_decimals – int (default: 100), optional

    Same as in get_vs.

  • big_p – int (default: 300), optional

    Same as in get_vs.

OUTPUT:

str

the table in Latex is issued.

EXAMPLES:

sage: from euler_product.lattice_invariant_euler_products import table_performance
sage: table_performance(10, 30) # random
11 102 digits for the first product
12 102 digits for the first product
13 102 digits for the first product
15 102 digits for the first product
16 102 digits for the first product
17 102 digits for the first product
19 102 digits for the first product
20 102 digits for the first product
21 102 digits for the first product
23 102 digits for the first product
24 102 digits for the first product
25 102 digits for the first product
27 102 digits for the first product
28 102 digits for the first product
29 102 digits for the first product
11& 10& 2& 8& 4& 21& 4 \
12& 4& 1& 5& 4& 21& 1 \
13& 12& 2& 10& 6& 21& 5 \
15& 8& 1& 5& 6& 21& 2 \
16& 8& 1& 5& 6& 21& 2 \
17& 16& 1& 5& 5& 21& 4 \
19& 18& 2& 10& 6& 21& 8 \
20& 8& 1& 5& 6& 21& 2 \
21& 12& 2& 10& 8& 21& 6 \
23& 22& 2& 6& 4& 21& 6 \
24& 8& 1& 5& 8& 21& 2 \
25& 20& 2& 8& 6& 21& 8 \
27& 18& 2& 10& 6& 21& 8 \
28& 12& 2& 10& 8& 21& 6 \
29& 28& 2& 7& 6& 21& 9 \

euler_product.utils_euler_product

Utils_euler_product utilities for Euler Product

utils_euler_product.py defines functions Main Engines

AUTHORS:

  • Olivier Ramaré (2023-01-008) : initial version

  • Dominique Benielli(2023-02_15) :

    Aix Marseille Université, Integration as SageMath package. Cellule de developpement Institut Archimède

Warning

Needs Sage version at least 9.0 CAREFUL, this is Python 3 code!

EXAMPLES:

sage: from euler_product.utils_euler_product import  LatticeInvariantClasses
class euler_product.utils_euler_product.ComponentStructure(q)[source]

Bases: object

This class takes a positive integer q and creates the following list of accessors:

  • phi_q: the value of the Euler-phi function at q.

  • the_exponent: the exponent of the multiplicative group \((\mathbb{Z}/q\mathbb{Z})^*\).

  • character_group: the group of Dirichlet characters modulo q, see this function for its description.

  • invertibles: the tuple of the integers between 1 and q that are prime to q.

  • the_SG_tuple and the_Class_tuple as in the class LatticeInvariantClass.

  • nb_class: the number of Lattice Invariant classes.

  • invariant_characters: given a subgroup in the_SG_tuple, the tuple of the characters that leaves this subgroup invariant is created. invariant_characters is this list of tuples, arranged as in the_SG_tuple.

  • getr_A_Kt: a method used only for get_CA_Km and get_CA_Km_F_sur_H.

    The coefficient C(A,K,m, F/H) are a sum on a variable t of s(F/H,m/t) times a function of t, say f(t). The lattice class A in given by its index ind_A in the_Class_tuple, the subgroup K is given by its index ind_K in the_SG_tuple. The function get_r_A_K_t answers a dictionary which to every (ind_A, ind_K, t) associates this f(t) (with the moebius factor). The list of t is of course limited and given as the input parameter of get_r_A_K_t. This is the list of elements that form a divisor-closed subset of integers. This list is the same as the list of necessary values of m.

  • get_CA_Km: a method used for get_vs.

    The coefficient C(A,K,m) are a sum on a variable t of a function of the value computed by getr_A_K_t. The lattice class A in given by its index ind_A in the_Class_tuple, the subgroup K is given by its index ind_K in the_SG_tuple. The function get_CA_Km answers a dictionary which to every (ind_A, ind_K, m) associates this value.

  • get_CA_Km_F_sur_H: a method used for get_euler_products.

    The coefficient C(A,K,m, F/H) are a sum on a variable t of s(F/H, m/t) times a function of the value computed by getr_A_K_t. The lattice class A in given by its index ind_A in the_Class_tuple, the subgroup K is given by its index ind_K in the_SG_tuple. The function get_CA_Km_F_sur_H answers a dictionary which to every (ind_A, ind_K, m) associates this value. When F == 1 and H == 1-X, the output of get_CA_Km_F_sur_H is the same as the one of get_CA_Km.

  • get_L_values: a method used only for get_gamma.

  • get_gamma: outputs the tuple defined in (22) of the corresponding paper.

    For every cyclic subgroup \(G_0\) in the_SG_tuple, we compute \(\sum_{\chi\in G_0^\perp} \log L_P(t*s, \chi)\), where \(L_P(x,\chi)\) is the L-series associated to \(\chi\), save that we remove the Euler factors for primes below P==big_p. The output is the list of these values computed with prec correct binary digits.

EXAMPLES:

sage: from euler_product.utils_euler_product import ComponentStructure
sage: structure = ComponentStructure(3)
get_CA_Km(my_indices)[source]

get_CA_Km is a method used for get_vs. The coefficient C(A,K,m) are a sum on a variable t of a function of the value computed by getr_A_K_t. The lattice class A in given by its index ind_A in the_Class_tuple, the subgroup K is given by its index ind_K in the_SG_tuple. The function get_CA_Km answers a dictionary which to every (ind_A, ind_K, m) associates this value.

INPUT:

  • my_indices – [int]

    list of indices (positive integers) m. It should be divisor-closed (and include 1) and ordered increasingly.

OUTPUT:

dictionary

outputs the dictionary (ind_A, ind_K, m) –> value, see above.

EXAMPLES:

sage: from euler_product.utils_euler_product import ComponentStructure
sage: from collections import OrderedDict
sage: structure = ComponentStructure(3)
sage: OrderedDict(structure.get_CA_Km([1, -4, 4, 2, -4, 1]))  # doctest: +ELLIPSIS, +NORMALIZE_WHITESPACE
OrderedDict([((0, 0, 1), 1/2), ((0, 0, -4), 1/2), ((0, 0, 4), 1/2), ((0, 0, 2), 1/2), ((0, 1, 1), 0), ((0, 1, -4), -1), ((0, 1, 4), -1), ((0, 1, 2), -1),
    ((1, 0, 1), -1/2), ((1, 0, -4), -1/2), ((1, 0, 4), -1/2), ((1, 0, 2), -1/2), ((1, 1, 1), 1), ((1, 1, -4), 1), ((1, 1, 4), 1), ((1, 1, 2), 1)])
get_CA_Km_F_sur_H(my_indices, coeff_sf, coeff_sh)[source]

get_CA_Km_F_sur_H: a method used for get_euler_products`. The coefficient C(A,K,m, F/H) are a sum on a variable t of s(F/H, m/t) times a function of the value computed by ``getr_A_K_t. The lattice class A in given by its index ind_A in the_Class_tuple, the subgroup K is given by its index ind_K in the_SG_tuple. The function get_CA_Km_F_sur_H answers a dictionary which to every (ind_A, ind_K, m) associates this value. When F == 1 and H == 1-X, the output of get_CA_Km_F_sur_H is the same as the one of get_CA_Km.

INPUT:

  • my_indices – list[int]

    list of indices (positive integers) m. It should be divisor-closed (and include 1) and ordered increasingly.

  • coeff_sf – list[float]

    the list of the sum of the m-th power of the inverses of the roots of F.

  • coeff_sh – [type]

    the list of the sum of the m-th power of the inverses of the roots of H.

OUTPUT

dictionary

outputs the dictionary (ind_A, ind_K, m) –> value, see above.

Examples

sage: from euler_product.utils_euler_product import ComponentStructure sage: structure = ComponentStructure(3) sage: structure.get_CA_Km_F_sur_H([1, 2, 3, 4, 5, 6], [1], [1, 0, -1]) # doctest: +NORMALIZE_WHITESPACE {(0, 0, 1): 0, (0, 0, 2): 1, (0, 0, 3): 0, (0, 0, 4): 1, (0, 0, 5): 0, (0, 0, 6): 0, (0, 1, 1): 0, (0, 1, 2): 0, (0, 1, 3): 0, (0, 1, 4): -2, (0, 1, 5): 0, (0, 1, 6): 0, (1, 0, 1): 0, (1, 0, 2): -1, (1, 0, 3): 0, (1, 0, 4): -1, (1, 0, 5): 0, (1, 0, 6): 0, (1, 1, 1): 0, (1, 1, 2): 2, (1, 1, 3): 0, (1, 1, 4): 2, (1, 1, 5): 0, (1, 1, 6): 0}

get_L_values(m, big_p, CIF, CF)[source]

for every Dirichlet character \(\chi\) modulo q, we compute the L-series \(L_P(m, \chi)\) associated to :math:chi:, save that we remove the Euler factors for primes below P==big_p. The output is the list of these values computed with prec correct binary digits.

INPUT:

  • m – [ComplexIntervalFieldElement]

    the point where the L-series are computed. The real part should be > 1 .

  • big_p – int

    a positive integer. The Euler products are computed for primes above big_p.

  • CIF – Complex Interval Field

    [description]

  • CF – Complex Field

    not used. Only CR.prec is used?

OUTPUT:

tuple

the tuple of the values of \(L_P(m,\chi)\), where \(\chi\) varies on the Dirichlet characters, values computed with prec correct binary digits.

EXCEPTIONS:

ValueError parameter m not in CIF

EXAMPLES:

sage: from euler_product.utils_euler_product import ComponentStructure
sage: structure = ComponentStructure(10)
sage: CIF = ComplexIntervalField(200)
sage: CF = ComplexField(200 + 1)
sage: m = CIF(2)
sage: structure.get_L_values(m, 200, CIF, CF)
(1.0007481024252386196893654501571877025514323183079093676480?,
1.0000226377974809104806639790897095274193344466859037418898? - 0.0000131408916900437454874106515694589606441168219958035059?*I,
0.9999899240511933872962748479693199723956317768469030922497? + 4.14392795471732850815599881400588351007002717820829591633?e-63*I,
1.0000226377974809104806639790897095274193344466859037418898? + 0.0000131408916900437454874106515694589606441168219958035059?*I)
sage: m = CIF(2.1)
sage: structure.get_L_values(m, 200, CIF, CF)
(1.0004029274879933694024714910876346995176209724918492580239?,
1.000013330852742794601876671961697811977029714891503324800? - 7.7538957108934769520297959484934618269499996602296768?e-6*I,
0.9999947644552454506994437910117325481790746758589349726959? + 3.15595539279556818499806833653635488946195252544140357784?e-63*I,
1.000013330852742794601876671961697811977029714891503324800? + 7.7538957108934769520297959484934618269499996602296768?e-6*I)
get_gamma(t, s, big_p, prec)[source]

Outputs the tuple defined in (22) of the corresponding paper: for every cyclic subgroup \(G_0\) in the_SG_tuple, we compute \(\sum_{\chi\in G_0^\perp} \log L_P(t*s, \chi)\), where \(L_P(x,\chi)\) is the L-series associated to \(\chi\), save that we remove the Euler factors for primes below P==big_p. The output is the list of these values computed with prec correct binary digits.

INPUT:

  • t – int

    the L-series are computed at t*s.

  • s – float

    the L-series are computed at t*s. The separation of t and s is only for readability of the code.

  • big_p – int

    a positive integer. The Euler products are computing for primes larger than big_p.

  • prec – int

    number of correct binary digits in the output.

OUTPUT:

tuple

the list of values of \(\sum_{\chi\in G_0^\perp} \log L_P(t*s, \chi)\), see the function description.

EXAMPLES:

sage: from euler_product.utils_euler_product import ComponentStructure
sage: structure  = ComponentStructure(5)
sage: structure.invariant_characters
((0, 1, 2, 3), (0, 2), (0,))
sage: structure.get_gamma(1, 1.2, 20, 100)
(0.412058674847838475387476473?, 0.3959326495526308567412224144?, 0.4113672762131896194520237806?)
getr_A_Kt(my_indices)[source]

This method is used only for get_CA_Km and get_CA_Km_F_sur_H. The coefficient C(A,K,m, F/H) are a sum on a variable t of s(F/H,m/t) times a function of t, say f(t). The lattice class A in given by its index ind_A in the_Class_tuple, the subgroup K is given by its index ind_K in the_SG_tuple. The function get_r_A_K_t answers a dictionary which to every (ind_A, ind_K, t) associates this f(t) (with the moebius factor). The list of t is of course limited and given as the input parameter of get_r_A_K_t. This is the list of elements that form a divisor-closed subset of integers. This list is the same as the list of necessary values of m.

INPUT:

  • my_indices – list

    list of indices (positive integers) t. It should be divisor-closed (and include 1) and ordered increasingly.

OUTPUT:

dictionary

output is a the dictionary (ind_A, ind_K, t) –> value, see above.

EXAMPLES:

sage: from euler_product.utils_euler_product import ComponentStructure
sage: structure = ComponentStructure(3)
sage: structure.getr_A_Kt([1, 2, 3, 4, 6])
{(0, 0, 1): 1/2,
(0, 0, 2): 0,
(0, 0, 3): -1/2,
(0, 0, 4): 0,
(0, 0, 6): 0,
(0, 1, 1): 0,
(0, 1, 2): -1,
(0, 1, 3): 0,
(0, 1, 4): 0,
(0, 1, 6): 1,
(1, 0, 1): -1/2,
(1, 0, 2): 0,
(1, 0, 3): 1/2,
(1, 0, 4): 0,
(1, 0, 6): 0,
(1, 1, 1): 1,
(1, 1, 2): 0,
(1, 1, 3): -1,
(1, 1, 4): 0,
(1, 1, 6): 0}
class euler_product.utils_euler_product.LatticeInvariantClasses[source]

Bases: object

This class takes a modulus q (i.e. a positive integer) and has two named accessors, the_SG_tuple and the_Class_tuple. The SG tuple is the list of the multiplicative subgroups of \((\mathbb{Z}/q\mathbb{Z})^*\) that are generated by a single element. The Class tuple is the list of Lattice Invariant classes, namely the partition of \((\mathbb{Z}/q\mathbb{Z})^*\) made by the smallest non-empty intersections of elements of the_SG_tuple.

EXAMPLES:

sage: from euler_product.utils_euler_product import LatticeInvariant
sage: LatticeInvariant(30)
((frozenset({1}),
  frozenset({1, 11}),
  frozenset({1, 19}),
  frozenset({1, 29}),
  frozenset({1, 7, 13, 19}),
  frozenset({1, 17, 19, 23})),
 (frozenset({1}),
  frozenset({11}),
  frozenset({19}),
  frozenset({29}),
  frozenset({7, 13}),
  frozenset({17, 23})))
euler_product.utils_euler_product.get_beta(F)[source]

Outputs the maximum of 1 and of the inverse of the norm of the non-zero roots of the polynomial F.

INPUT:

  • F – pol

    a polynomial with RealField coefficients.

OUTPUT:

float

the maximum of 1 and of the inverse of the norm of the non-zero roots of F.

EXAMPLES:

sage: from euler_product.utils_euler_product import get_beta
sage: R0 = RealField(30)
sage: R0X = R0['x']
sage: (x,) = R0X._first_ngens(1)
sage: F0 = R0X(1 - x^2)
sage: get_beta(F0)
1
euler_product.utils_euler_product.get_beta_rough(coeffs_f)[source]

Outputs the maximum of 1 and of the sum of the norm of the coefficients of the polynomial F, which is precisely given as the list coeffs_f. This is intended to be an easy upper bound when the function get_beta takes too much time.

INPUT:

  • coeffs_f – float

    a list of floats, supposedly representing a polynomial F.

OUTPUT:

float

Outputs the maximum of 1 and of the sum of the norm of the elements of coeffs_f.

EXAMPLES:

sage: from euler_product.utils_euler_product import get_beta_rough
sage: get_beta_rough([1, 3, 4])
8
euler_product.utils_euler_product.get_vector_sf(coeffs_f, how_many)[source]

A polynomial F is given by its list of coefficients, the first one being 1. The output is the list \(s_F(m)\) for m less than how_many, where \(s_F(m)\) is the sum of the m-th power of the inverses of the roots of F.

INPUT:

  • coeffs_f – list[float]

    coefficients of the polynomial f, starting by 1.

  • how_many – int

    number of computed coefficients.

OUTPUT:

list

list des coefficient s_f(m) over m <= how_many.

EXAMPLES:

sage: from euler_product.utils_euler_product import get_vector_sf
sage: get_vector_sf([1, -1], 5)
[1, 1, 1, 1, 1]
sage: get_vector_sf([1, 1, 1], 10)
[2, -1, -1, 2, -1, -1, 2, -1, -1, 2]
euler_product.utils_euler_product.laTeX_for_number(w, how_many, nb_block_sto_cut)[source]

Return a character string representing the real number w made of its integer part followed by every decimal up to the``how_many`` -th decimals, where every block of 5 decimal is separated by '\\,', and every succession of how_many blocks is separated by '\n'. The string has a `&` after the decimal point and ends with the string `\\cdots`.

INPUT:

  • w – float

    w is a real number with a (short) integer part and a floating point.

  • how_many – int

    number of decimals, separated every 5 of them by '\,' and every block of nb_block_sto_cut, on a different line. ‘\cdots’ ends the string.

  • nb_block_sto_cut – int

    See above.

OUTPUT:

str

a character string int(w).separated_decimals where separated_decimals is LaTeX formatted version of the decimal expansion of w, see the description of the function.

EXAMPLES:

sage: from euler_product.utils_euler_product import laTeX_for_number
sage: laTeX_for_number(22.01234567812345, 100, 8)
'22.&01234\\,56781\\,235\\cdots'
euler_product.utils_euler_product.nb_common_digits(a, b)[source]

Returns -1 if floor(a) != floor(b).

INPUT:

  • a – float

    first float to compare.

  • b – float

    second float to compare.

OUTPUT:

int

Returns -1 if floor(a) != floor(b), or the number of common digits.

EXAMPLES:

sage: from euler_product.utils_euler_product import nb_common_digits
sage: import numpy as np
sage: nb_common_digits(1.33333, 1.334444)
2
sage: nb_common_digits(1.33333, 2.334444)
-1
sage: nb_common_digits(1.33333, np.inf)
-1
sage: nb_common_digits(np.inf, np.nan)
-1
euler_product.utils_euler_product.sub_group_generated(n, q)[source]

Return the frozenset of the multiplicative subgroup generated by the powers of n modulo q. It is expected that n and q are coprime.

INPUT:

  • n – int

    an integer, expected to be coprime to q.

  • q – int

    a positive integer.

OUTPUT:

frozenset

immutable set of the powers of n modulo q

EXAMPLES:

sage: from euler_product.utils_euler_product import sub_group_generated
sage: sub_group_generated(5, 3)
frozenset({1, 2})