Merge lp:~maddm/maddm/as_running into lp:maddm

Proposed by Olivier Mattelaer
Status: Merged
Merged at revision: 22
Proposed branch: lp:~maddm/maddm/as_running
Merge into: lp:maddm
Diff against target: 416 lines (+311/-9)
8 files modified
Templates/Cards/maddm_card.dat (+4/-0)
Templates/src/alfas.inc (+11/-0)
Templates/src/alfas_functions.f (+280/-0)
Templates/src/init.f (+8/-0)
Templates/src/maddm.f (+3/-0)
Templates/src/makefile (+2/-9)
maddm_run_interface.py (+1/-0)
python_templates/maddm.inc (+2/-0)
To merge this branch: bzr merge lp:~maddm/maddm/as_running
Reviewer Review Type Date Requested Status
Olivier Mattelaer Pending
Review via email: mp+380412@code.launchpad.net

Commit message

as running

To post a comment you must log in.

Preview Diff

[H/L] Next/Prev Comment, [J/K] Next/Prev File, [N/P] Next/Prev Hunk
1=== modified file 'Templates/Cards/maddm_card.dat'
2--- Templates/Cards/maddm_card.dat 2018-03-14 15:19:47 +0000
3+++ Templates/Cards/maddm_card.dat 2020-03-09 09:47:54 +0000
4@@ -41,6 +41,10 @@
5 # (see manual for more details). Slower, but more accurate.
6 %(xd_approx)s = xd_approx
7
8+# choose whether to run the strong coupling up to the energy scale given by 2*m_chi
9+# if False, alpha_s is read from the param_card
10+ %(running_as)s = running_as
11+
12 ###################################################################################
13 #
14 # Direct(ional) Detection
15
16=== added file 'Templates/src/alfas.inc'
17--- Templates/src/alfas.inc 1970-01-01 00:00:00 +0000
18+++ Templates/src/alfas.inc 2020-03-09 09:47:54 +0000
19@@ -0,0 +1,11 @@
20+c***********************************************************************
21+c this files contains the common blocks for the
22+c the alpha_s settings
23+c
24+c asmz = alpha_s(Mz) is set based on the pdf chosen in setcuts.f
25+c nloop = order of the running of alpha_s based on the pdf chosen
26+c***********************************************************************
27+ integer nloop
28+ double precision asmz
29+ common/a_block/asmz,nloop
30+
31
32=== added file 'Templates/src/alfas_functions.f'
33--- Templates/src/alfas_functions.f 1970-01-01 00:00:00 +0000
34+++ Templates/src/alfas_functions.f 2020-03-09 09:47:54 +0000
35@@ -0,0 +1,280 @@
36+C
37+C-----------------------------------------------------------------------------
38+C
39+ double precision function alfa(alfa0,qsq )
40+C
41+C-----------------------------------------------------------------------------
42+C
43+C This function returns the 1-loop value of alpha.
44+C
45+C INPUT:
46+C qsq = Q^2
47+C
48+C-----------------------------------------------------------------------------
49+C
50+ implicit none
51+ double precision qsq,alfa0
52+c
53+c constants
54+c
55+ double precision One, Three, Pi,zmass
56+ parameter( One = 1.0d0, Three = 3.0d0 )
57+ parameter( Pi = 3.14159265358979323846d0 )
58+ parameter( zmass = 91.188d0 )
59+cc
60+ alfa = alfa0 / ( 1.0d0 - alfa0*dlog( qsq/zmass**2 ) /Three /Pi )
61+ccc
62+ return
63+ end
64+
65+C
66+C-----------------------------------------------------------------------------
67+C
68+ double precision function alfaw(alfaw0,qsq,nh )
69+C
70+C-----------------------------------------------------------------------------
71+C
72+C This function returns the 1-loop value of alpha_w.
73+C
74+C INPUT:
75+C qsq = Q^2
76+C nh = # of Higgs doublets
77+C
78+C-----------------------------------------------------------------------------
79+C
80+ implicit none
81+ double precision qsq, alphaw, dum,alfaw0
82+ integer nh, nq
83+c
84+c include
85+c
86+
87+c
88+c constants
89+c
90+ double precision Two, Four, Pi, Twpi, zmass,tmass
91+ parameter( Two = 2.0d0, Four = 4.0d0 )
92+ parameter( Pi = 3.14159265358979323846d0 )
93+ parameter( Twpi = 3.0d0*Four*Pi )
94+ parameter( zmass = 91.188d0,tmass=174d0 )
95+cc
96+ if ( qsq.ge.tmass**2 ) then
97+ nq = 6
98+ else
99+ nq = 5
100+ end if
101+ dum = ( 22.0d0 - Four*nq - nh/Two ) / Twpi
102+ alfaw = alfaw0 / ( 1.0d0 + dum*alfaw0*dlog( qsq/zmass**2 ) )
103+ccc
104+ return
105+ end
106+
107+C-----------------------------------------------------------------------------
108+C
109+ DOUBLE PRECISION FUNCTION ALPHAS(Q)
110+c
111+c Evaluation of strong coupling constant alpha_S
112+c Author: R.K. Ellis
113+c
114+c q -- scale at which alpha_s is to be evaluated
115+c
116+c-- common block alfas.inc
117+c asmz -- value of alpha_s at the mass of the Z-boson
118+c nloop -- the number of loops (1,2, or 3) at which beta
119+c
120+c function is evaluated to determine running.
121+c the values of the cmass and the bmass should be set
122+c in common block qmass.
123+C-----------------------------------------------------------------------------
124+
125+ IMPLICIT NONE
126+c
127+ include 'alfas.inc'
128+ DOUBLE PRECISION Q,T,AMZ0,AMB,AMC
129+ DOUBLE PRECISION AS_OUT
130+ INTEGER NLOOP0,NF3,NF4,NF5
131+ PARAMETER(NF5=5,NF4=4,NF3=3)
132+C
133+ REAL*8 CMASS,BMASS
134+ COMMON/QMASS/CMASS,BMASS
135+ DATA CMASS,BMASS/1.42D0,4.7D0/ ! HEAVY QUARK MASSES FOR THRESHOLDS
136+C
137+ REAL*8 ZMASS
138+ DATA ZMASS/91.188D0/
139+C
140+ SAVE AMZ0,NLOOP0,AMB,AMC
141+ DATA AMZ0,NLOOP0/0D0,0/
142+ IF (Q .LE. 0D0) THEN
143+ WRITE(6,*) 'q .le. 0 in alphas'
144+ WRITE(6,*) 'q= ',Q
145+ STOP
146+ ENDIF
147+ IF (asmz .LE. 0D0) THEN
148+ WRITE(6,*) 'asmz .le. 0 in alphas',asmz
149+c WRITE(6,*) 'continue with asmz=0.1185'
150+ STOP
151+ asmz=0.1185D0
152+ ENDIF
153+ IF (CMASS .LE. 0.3D0) THEN
154+ WRITE(6,*) 'cmass .le. 0.3GeV in alphas',CMASS
155+c WRITE(6,*) 'continue with cmass=1.5GeV?'
156+ STOP
157+ CMASS=1.42D0
158+ ENDIF
159+ IF (BMASS .LE. 0D0) THEN
160+ WRITE(6,*) 'bmass .le. 0 in alphas',BMASS
161+ WRITE(6,*) 'COMMON/QMASS/CMASS,BMASS'
162+ STOP
163+ BMASS=4.7D0
164+ ENDIF
165+c--- establish value of coupling at b- and c-mass and save
166+ IF ((asmz .NE. AMZ0) .OR. (NLOOP .NE. NLOOP0)) THEN
167+ AMZ0=asmz
168+ NLOOP0=NLOOP
169+ T=2D0*DLOG(BMASS/ZMASS)
170+ CALL NEWTON1(T,asmz,AMB,NLOOP,NF5)
171+ T=2D0*DLOG(CMASS/BMASS)
172+ CALL NEWTON1(T,AMB,AMC,NLOOP,NF4)
173+ ENDIF
174+
175+c--- evaluate strong coupling at scale q
176+ IF (Q .LT. BMASS) THEN
177+ IF (Q .LT. CMASS) THEN
178+ T=2D0*DLOG(Q/CMASS)
179+ CALL NEWTON1(T,AMC,AS_OUT,NLOOP,NF3)
180+ ELSE
181+ T=2D0*DLOG(Q/BMASS)
182+ CALL NEWTON1(T,AMB,AS_OUT,NLOOP,NF4)
183+ ENDIF
184+ ELSE
185+ T=2D0*DLOG(Q/ZMASS)
186+ CALL NEWTON1(T,asmz,AS_OUT,NLOOP,NF5)
187+ ENDIF
188+ ALPHAS=AS_OUT
189+ RETURN
190+ END
191+
192+
193+ SUBROUTINE NEWTON1(T,A_IN,A_OUT,NLOOP,NF)
194+C Author: R.K. Ellis
195+
196+c--- calculate a_out using nloop beta-function evolution
197+c--- with nf flavours, given starting value as-in
198+c--- given as_in and logarithmic separation between
199+c--- input scale and output scale t.
200+c--- Evolution is performed using Newton's method,
201+c--- with a precision given by tol.
202+
203+ IMPLICIT NONE
204+ INTEGER NLOOP,NF
205+ REAL*8 T,A_IN,A_OUT,AS,TOL,F2,F3,F,FP,DELTA
206+ REAL*8 B0(3:5),C1(3:5),C2(3:5),DEL(3:5)
207+ PARAMETER(TOL=5.D-4)
208+C--- B0=(11.-2.*NF/3.)/4./PI
209+ DATA B0/0.716197243913527D0,0.66314559621623D0,0.61009394851893D0/
210+C--- C1=(102.D0-38.D0/3.D0*NF)/4.D0/PI/(11.D0-2.D0/3.D0*NF)
211+ DATA C1/.565884242104515D0,0.49019722472304D0,0.40134724779695D0/
212+C--- C2=(2857.D0/2.D0-5033*NF/18.D0+325*NF**2/54)
213+C--- /16.D0/PI**2/(11.D0-2.D0/3.D0*NF)
214+ DATA C2/0.453013579178645D0,0.30879037953664D0,0.14942733137107D0/
215+C--- DEL=SQRT(4*C2-C1**2)
216+ DATA DEL/1.22140465909230D0,0.99743079911360D0,0.66077962451190D0/
217+ F2(AS)=1D0/AS+C1(NF)*LOG((C1(NF)*AS)/(1D0+C1(NF)*AS))
218+ F3(AS)=1D0/AS+0.5D0*C1(NF)
219+ & *LOG((C2(NF)*AS**2)/(1D0+C1(NF)*AS+C2(NF)*AS**2))
220+ & -(C1(NF)**2-2D0*C2(NF))/DEL(NF)
221+ & *ATAN((2D0*C2(NF)*AS+C1(NF))/DEL(NF))
222+
223+
224+ A_OUT=A_IN/(1D0+A_IN*B0(NF)*T)
225+ IF (NLOOP .EQ. 1) RETURN
226+ A_OUT=A_IN/(1D0+B0(NF)*A_IN*T+C1(NF)*A_IN*LOG(1D0+A_IN*B0(NF)*T))
227+ IF (A_OUT .LT. 0D0) AS=0.3D0
228+ 30 AS=A_OUT
229+
230+ IF (NLOOP .EQ. 2) THEN
231+ F=B0(NF)*T+F2(A_IN)-F2(AS)
232+ FP=1D0/(AS**2*(1D0+C1(NF)*AS))
233+ ENDIF
234+ IF (NLOOP .EQ. 3) THEN
235+ F=B0(NF)*T+F3(A_IN)-F3(AS)
236+ FP=1D0/(AS**2*(1D0+C1(NF)*AS+C2(NF)*AS**2))
237+ ENDIF
238+ A_OUT=AS-F/FP
239+ DELTA=ABS(F/FP/AS)
240+ IF (DELTA .GT. TOL) GO TO 30
241+ RETURN
242+ END
243+
244+
245+C-----------------------------------------------------------------------------
246+C
247+ double precision function mfrun(mf,scale,asmz,nloop)
248+C
249+C-----------------------------------------------------------------------------
250+C
251+C This function returns the 2-loop value of a MSbar fermion mass
252+C at a given scale.
253+C
254+C INPUT: mf = MSbar mass of fermion at MSbar fermion mass scale
255+C scale = scale at which the running mass is evaluated
256+C asmz = AS(MZ) : this is passed to alphas(scale,asmz,nloop)
257+C nloop = # of loops in the evolution
258+C
259+C
260+C
261+C EXTERNAL: double precision alphas(scale,asmz,nloop)
262+C
263+C-----------------------------------------------------------------------------
264+C
265+ implicit none
266+C
267+C ARGUMENTS
268+C
269+ double precision mf,scale,asmz
270+ integer nloop
271+C
272+C LOCAL
273+C
274+ double precision beta0, beta1,gamma0,gamma1
275+ double precision A1,as,asmf,l2
276+ integer nf
277+C
278+C EXTERNAL
279+C
280+ double precision alphas
281+ external alphas
282+c
283+c CONSTANTS
284+c
285+ double precision One, Two, Three, Pi
286+ parameter( One = 1.0d0, Two = 2.0d0, Three = 3.0d0 )
287+ parameter( Pi = 3.14159265358979323846d0)
288+ double precision tmass
289+ parameter(tmass=174d0)
290+cc
291+C
292+C
293+ if ( mf.gt.tmass ) then
294+ nf = 6
295+ else
296+ nf = 5
297+ end if
298+
299+ beta0 = ( 11.0d0 - Two/Three *nf )/4d0
300+ beta1 = ( 102d0 - 38d0/Three*nf )/16d0
301+ gamma0= 1d0
302+ gamma1= ( 202d0/3d0 - 20d0/9d0*nf )/16d0
303+ A1 = -beta1*gamma0/beta0**2+gamma1/beta0
304+ as = alphas(scale)
305+ asmf = alphas(mf)
306+ l2 = (1+ A1*as/Pi)/(1+ A1*asmf/Pi)
307+
308+
309+ mfrun = mf * (as/asmf)**(gamma0/beta0)
310+
311+ if(nloop.eq.2) mfrun =mfrun*l2
312+ccc
313+ return
314+ end
315+
316
317=== modified file 'Templates/src/init.f'
318--- Templates/src/init.f 2019-05-03 21:09:49 +0000
319+++ Templates/src/init.f 2020-03-09 09:47:54 +0000
320@@ -14,6 +14,8 @@
321 implicit none
322 include 'maddm.inc'
323 include 'coupl.inc'
324+ double precision alphas
325+ external alphas
326
327 c parameters used in this subroutine only
328 character*30 filename
329@@ -49,6 +51,12 @@
330
331 include 'process_names.inc'
332
333+c Run alpha_s for the relic
334+
335+ if (running_as) then
336+ call UPDATE_AS_PARAM2(0, alphas(2*mdm(1)))
337+ endif
338+
339 c initialize the arrays for the relativistic degrees of freedom
340 filename = 'include/fermion.txt'
341 call readinfile(filename,401,gstar_x,gstar_fermion)
342
343=== modified file 'Templates/src/maddm.f'
344--- Templates/src/maddm.f 2018-03-28 21:20:11 +0000
345+++ Templates/src/maddm.f 2020-03-09 09:47:54 +0000
346@@ -10,6 +10,7 @@
347 include 'maddm.inc'
348 include 'input.inc'
349 include 'coupl.inc'
350+ include 'alfas.inc'
351
352 c parameters used in this routine only
353 Integer sm_flag, prnt_tag, k, ii
354@@ -28,6 +29,8 @@
355
356 c Sets all the parameters used in MG/ME to the values in the param card
357 call setpara('Cards/param_card.dat')
358+ asmz=as
359+ nloop=2
360
361 c If the user wants to change any of the parameters from within the fortran code then
362 c just change the variables given in 'input.inc' and simply run the subroutine coup()
363
364=== modified file 'Templates/src/makefile'
365--- Templates/src/makefile 2019-05-02 18:56:32 +0000
366+++ Templates/src/makefile 2020-03-09 09:47:54 +0000
367@@ -9,22 +9,15 @@
368
369 libs = -lmatrix_elements -ldhelas -lmodel
370
371-objs_all=init.o integrate.o interpolate.o maddm.o phasespace.o relic_canon.o relic_coupled.o relic_density.o direct_detection.o directional_detection.o indirect_detect_2to2.o tests.o capture_rate.o
372+objs_all=init.o integrate.o interpolate.o maddm.o phasespace.o relic_canon.o relic_coupled.o relic_density.o direct_detection.o directional_detection.o indirect_detect_2to2.o tests.o capture_rate.o alfas_functions.o
373
374 #Dependencies
375-init.o: $(incdir)/maddm.inc $(incdir)/maddm_card.inc
376-integrate.o: $(incdir)/maddm.inc $(incdir)/maddm_card.inc
377-interpolate.o: $(incdir)/maddm.inc $(incdir)/maddm_card.inc
378 maddm.x: $(incdir)/maddm.inc $(incdir)/maddm_card.inc
379-phasespace.o: $(incdir)/maddm.inc $(incdir)/maddm_card.inc
380-relic_canon.o: $(incdir)/maddm.inc $(incdir)/maddm_card.inc
381-relic_coupled.o: $(incdir)/maddm.inc $(incdir)/maddm_card.inc
382-relic_density.o: $(incdir)/maddm.inc $(incdir)/maddm_card.inc
383 direct_detection.o: $(incdir)/maddm.inc $(incdir)/maddm_card.inc
384 directional_detection.o: $(incdir)/maddm.inc $(incdir)/maddm_card.inc
385-indirect_detect_2to2.o: $(incdir)/maddm.inc $(incdir)/maddm_card.inc
386 capture_rate.o: $(incdir)/maddm.inc $(incdir)/capturerate_models.inc
387 tests.o: $(incdir)/maddm.inc $(incdir)/maddm_card.inc
388+maddm.o: $(incdir)/maddm.inc $(incdir)/maddm_card.inc
389
390 all: maddm
391
392
393=== modified file 'maddm_run_interface.py'
394--- maddm_run_interface.py 2019-12-19 11:40:12 +0000
395+++ maddm_run_interface.py 2020-03-09 09:47:54 +0000
396@@ -3188,6 +3188,7 @@
397
398 self.add_param('eps_ode', 0.01)
399 self.add_param('xd_approx', False)
400+ self.add_param('running_as', True, comment='choose whether to run the strong coupling up to 2*m_chi energy scale', include=True)
401
402 self.add_param('x_start', 50.0, hidden=True)
403 self.add_param('x_end', 1000.0, hidden=True)
404
405=== modified file 'python_templates/maddm.inc'
406--- python_templates/maddm.inc 2019-05-03 21:09:49 +0000
407+++ python_templates/maddm.inc 2020-03-09 09:47:54 +0000
408@@ -19,6 +19,8 @@
409 double precision taacs_coupled, taacs_integrand
410 c relic_density.f
411 double precision relic_density, approximate_xd
412+ logical running_as
413+ common/idrelic_running/ running_as
414 c tests.f
415 double precision crossijk, cross_check_process
416 c indirect_detection.f

Subscribers

People subscribed via source and target branches

to all changes: