Skip to content

Commit

Permalink
Use low scale constraint to set model parameters from SM parameters
Browse files Browse the repository at this point in the history
This is, however, a very bad hack to achieve this, and needs to be
refined.  In particular, for consistency with SPheno, only
parameters depending on the gauge and Yukawa couplings should be
updated.  As part of this the ordering must be done correctly
to ensure e.g. the correct on-shell VEV is set.  Temporary
settings and macros must also be handled.
  • Loading branch information
Dylan Harries committed Mar 4, 2016
1 parent befca5e commit ee58b39
Show file tree
Hide file tree
Showing 4 changed files with 193 additions and 64 deletions.
128 changes: 78 additions & 50 deletions meta/EffectiveCouplings.m
@@ -1,11 +1,11 @@
BeginPackage["EffectiveCouplings`", {"SARAH`", "CConversion`", "Parameters`", "SelfEnergies`", "TreeMasses`", "TextFormatting`", "Utils`", "Vertices`", "Observables`"}];
BeginPackage["EffectiveCouplings`", {"SARAH`", "CConversion`", "Parameters`", "SelfEnergies`", "TreeMasses`", "TextFormatting`", "Utils`", "Vertices`", "Observables`", "Constraint`"}];

InitializeEffectiveCouplings::usage="";
InitializeMixingFromModelInput::usage="";
GetMixingMatrixFromModel::usage="";
CreateSMRunningFunctions::usage="";
CreateSMGaugeRunningFunctions::usage="";
GetNeededVerticesList::usage="";
GetSMParameterReplacements::usage="";
SetModelParametersFromSM::usage="";
CalculatePartialWidths::usage="";
CalculateQCDAmplitudeScalingFactors::usage="";
CalculateQCDScalingFactor::usage="";
Expand Down Expand Up @@ -382,53 +382,81 @@ previous results (e.g. define along the lines of f[p] := f[p] = ...) *)
init
];

CreateSMRunningFunctions[settings_List] :=
Module[{body = "", prototype = "", function = ""},
If[!SARAH`SupersymmetricModel,
prototype = "void run_SM_parameters_to(double m);\n";
body = "using namespace standard_model;\n\nStandard_model sm;\n\n";
body = body <>
"sm.set_loops(2);\n" <>
"sm.set_thresholds(0);\n" <>
"sm.set_low_energy_data(qedqcd);\n" <>
"sm.set_physical_input(physical_input);\n\n";
body = body <> "sm.initialise_from_input();\n"
<> "sm.run_to(m);\n\n";
(* for effective couplings the on-shell SM vev and top mass are used *)
body = body <> "// ensure on-shell SM vev and top mass\n"
<> "sm.set_v(1.0 / Sqrt(qedqcd.displayFermiConstant() * Sqrt(2.0)));\n"
<> "sm.set_Yu(2, 2, -Sqrt(2.0) * qedqcd.displayPoleMt() / sm.get_v());\n"
<> "sm.calculate_DRbar_masses();\n\n";

(* update parameters depending on SM gauge and Yukawa couplings *)

function = "void " <> FlexibleSUSY`FSModelName
<> "_effective_couplings::run_SM_parameters_to(double m)\n{\n"
<> TextFormatting`IndentText[body] <> "\n}\n";
];
{prototype, function}
];

CreateSMGaugeRunningFunctions[] :=
Module[{body = "", prototype = "", function = ""},
If[ValueQ[SARAH`hyperchargeCoupling] && ValueQ[SARAH`leftCoupling] &&
ValueQ[SARAH`strongCoupling],
prototype = "void run_SM_strong_coupling_to(double m);\n";
body = "using namespace standard_model;\n\nStandard_model sm;\n\n";
body = body <>
"sm.set_loops(2);\n" <>
"sm.set_thresholds(0);\n" <>
"sm.set_low_energy_data(qedqcd);\n" <>
"sm.set_physical_input(physical_input);\n\n";
body = body <> "sm.initialise_from_input();\nsm.run_to(m);\n\n";
body = body <> "model.set_"
<> CConversion`ToValidCSymbolString[SARAH`strongCoupling]
<> "(sm.get_g3());";
function = "void " <> FlexibleSUSY`FSModelName
<> "_effective_couplings::run_SM_strong_coupling_to(double m)\n{\n"
<> TextFormatting`IndentText[body] <> "\n}\n";
];
{prototype, function}
DependsOnSMCouplings[{parameter_, value_}] :=
Module[{smVev, smSyms},
smVev = Parameters`GetParameterFromDescription["EW-VEV"];
smSyms = {SARAH`UpYukawa, SARAH`DownYukawa, SARAH`ElectronYukawa,
FlexibleSUSY`LowEnergyConstant, FlexibleSUSY`LowEnergyGaugeCoupling};
If[ValueQ[SARAH`hyperchargeCoupling], smSyms = Append[smSyms, SARAH`hyperchargeCoupling];];
If[ValueQ[SARAH`leftCoupling], smSyms = Append[smSyms, SARAH`leftCoupling];];
If[ValueQ[SARAH`strongCoupling], smSyms = Append[smSyms, SARAH`strongCoupling];];
If[smVev =!= Null, smSyms = Append[smSyms, smVev];];
!(And @@ FreeQ[value, #]& /@ smSyms)
];

DependsOnSMCouplings[FlexibleSUSY`FSSolveEWSBFor[__]] := True;

DependsOnSMCouplings[setting_] := False;

GetSMParameterReplacements[] :=
{"LowEnergyConstant(gYSM)" :> "Sqrt(3./5.) * sm->get_g1()",
"LowEnergyConstant(g1SM)" :> "sm->get_g1()",
"LowEnergyConstant(g2SM)" :> "sm->get_g2()",
"LowEnergyConstant(g3SM)" :> "sm->get_g3()",
"LowEnergyConstant(yeSM)" :> "sm->get_Ye(0,0)",
"LowEnergyConstant(ymSM)" :> "sm->get_Ye(1,1)",
"LowEnergyConstant(ylSM)" :> "sm->get_Ye(2,2)",
"LowEnergyConstant(yuSM)" :> "sm->get_Yu(0,0)",
"LowEnergyConstant(ycSM)" :> "sm->get_Yu(1,1)",
"LowEnergyConstant(ytSM)" :> "sm->get_Yu(2,2)",
"LowEnergyConstant(ydSM)" :> "sm->get_Yd(0,0)",
"LowEnergyConstant(ysSM)" :> "sm->get_Yd(1,1)",
"LowEnergyConstant(ybSM)" :> "sm->get_Yd(2,2)",
"LowEnergyConstant(mu2SM)" :> "sm->get_mu2()",
"LowEnergyConstant(lamSM)" :> "sm->get_Lambdax()",
"LowEnergyConstant(vSM)" :> "sm->get_v()"
};

ApplyLowScaleConstraint[{parameter_ | parameter_[__] /; parameter === SARAH`UpYukawa,
value_ /; (!FreeQ[value, Global`topDRbar] || value === Automatic)},
modelName_String] :=
"set_" <> CConversion`ToValidCSymbolString[parameter] <> "_from_SM();\n";

ApplyLowScaleConstraint[{parameter_ | parameter_[__] /; parameter === SARAH`DownYukawa,
value_ /; (!FreeQ[value, Global`bottomDRbar] || value === Automatic)},
modelName_String] :=
"set_" <> CConversion`ToValidCSymbolString[parameter] <> "_from_SM();\n";

ApplyLowScaleConstraint[{parameter_ | parameter_[__] /; parameter === SARAH`ElectronYukawa,
value_ /; (!FreeQ[value, Global`electronDRbar] || value === Automatic)},
modelName_String] :=
"set_" <> CConversion`ToValidCSymbolString[parameter] <> "_from_SM();\n";


SetModelParametersFromSM[settings_List] :=
Module[{result = "", smSettings = settings, noMacros, noTemp},
smSettings = smSettings /. {"new_g1" -> "sm->get_g1()",
"new_g2" -> "sm->get_g2()",
"new_g3" -> "sm->get_g3()"};
result = Constraint`ApplyConstraints[smSettings];
result = StringReplace[result,
{Shortest["INPUTPARAMETER(" ~~ p__ ~~ ")"] :> "MODEL->get_input()." <> p,
Shortest["MODELPARAMETER(" ~~ p__ ~~ ")"] :> "MODEL->get_" <> p <> "()",
Shortest["DERIVEDPARAMETER(" ~~ p__ ~~ ")"] :> "MODEL->" <> p <> "()",
Shortest["PHASE(" ~~ p__ ~~ ")"] :> "MODEL->get_" <> p <> "()",
Shortest["PHYSICAL(" ~~ p__ ~~ ")"] :> "MODEL->get_physical()." <> p,
"calculate_" <> CConversion`ToValidCSymbolString[SARAH`UpYukawa]
<> "_DRbar()" :> "set_" <> CConversion`ToValidCSymbolString[SARAH`UpYukawa]
<> "_from_SM()",
"calculate_" <> CConversion`ToValidCSymbolString[SARAH`DownYukawa]
<> "_DRbar()" :> "set_" <> CConversion`ToValidCSymbolString[SARAH`DownYukawa]
<> "_from_SM()",
"calculate_" <> CConversion`ToValidCSymbolString[SARAH`ElectronYukawa]
<> "_DRbar()" :> "set_" <> CConversion`ToValidCSymbolString[SARAH`ElectronYukawa]
<> "_from_SM()"
}];
result = StringReplace[result, GetSMParameterReplacements[]];
result
];

RunToDecayingParticleScale[scale_] :=
Expand Down
26 changes: 18 additions & 8 deletions meta/FlexibleSUSY.m
Expand Up @@ -1103,16 +1103,25 @@ corresponding tadpole is real or imaginary (only in models with CP
Module[{i, partialWidthGetterPrototypes, partialWidthGetters,
loopCouplingsGetters, loopCouplingsDefs, mixingMatricesDefs = "",
loopCouplingsInit, mixingMatricesInit = "", copyMixingMatrices = "",
runSMParametersPrototype, runSMParametersFunction,
runSMGaugeCouplingsPrototype, runSMGaugeCouplingsFunction,
setSMStrongCoupling = "", applyLowScaleConstraint = "", setDRbarYukawaCouplings = "",
calculateScalarScalarLoopQCDFactor, calculateScalarFermionLoopQCDFactor,
calculatePseudocalarFermionLoopQCDFactor,
calculateScalarQCDScalingFactor, calculatePseudoscalarQCDScalingFactor,
calculateLoopCouplings, loopCouplingsPrototypes,
loopCouplingsFunctions},
{partialWidthGetterPrototypes, partialWidthGetters} = EffectiveCouplings`CalculatePartialWidths[couplings];
{runSMParametersPrototype, runSMParametersFunction} = EffectiveCouplings`CreateSMRunningFunctions[settings];
{runSMGaugeCouplingsPrototype, runSMGaugeCouplingsFunction} = EffectiveCouplings`CreateSMGaugeRunningFunctions[];
If[ValueQ[SARAH`strongCoupling],
setSMStrongCoupling = "model.set_" <> CConversion`ToValidCSymbolString[SARAH`strongCoupling] <> "(sm.get_g3());\n";
];
applyLowScaleConstraint = EffectiveCouplings`SetModelParametersFromSM[settings];
setDRbarYukawaCouplings = {
ThresholdCorrections`SetDRbarYukawaCouplingTop[settings],
ThresholdCorrections`SetDRbarYukawaCouplingBottom[settings],
ThresholdCorrections`SetDRbarYukawaCouplingElectron[settings]
};
setDRbarYukawaCouplings = StringReplace[#, Shortest["MODELPARAMETER(" ~~ p__ ~~ ")"] :> "MODEL->get_" <> p <> "()"]&
/@ setDRbarYukawaCouplings;
setDRbarYukawaCouplings = StringReplace[#, EffectiveCouplings`GetSMParameterReplacements[]]& /@ setDRbarYukawaCouplings;
loopCouplingsGetters = EffectiveCouplings`CreateEffectiveCouplingsGetters[couplings];
For[i = 1, i <= Length[massMatrices], i++,
mixingMatricesDefs = mixingMatricesDefs <> TreeMasses`CreateMixingMatrixDefinition[massMatrices[[i]]];
Expand All @@ -1134,15 +1143,16 @@ corresponding tadpole is real or imaginary (only in models with CP
"@partialWidthGetters@" -> partialWidthGetters,
"@loopCouplingsGetters@" -> IndentText[loopCouplingsGetters],
"@loopCouplingsPrototypes@" -> IndentText[loopCouplingsPrototypes],
"@runSMParametersPrototype@" -> IndentText[runSMParametersPrototype],
"@runSMGaugeCouplingsPrototype@" -> IndentText[runSMGaugeCouplingsPrototype],
"@mixingMatricesDefs@" -> IndentText[mixingMatricesDefs],
"@loopCouplingsDefs@" -> IndentText[loopCouplingsDefs],
"@mixingMatricesInit@" -> IndentText[WrapLines[mixingMatricesInit]],
"@loopCouplingsInit@" -> IndentText[WrapLines[loopCouplingsInit]],
"@copyMixingMatrices@" -> IndentText[copyMixingMatrices],
"@runSMParametersFunction@" -> runSMParametersFunction,
"@runSMGaugeCouplingsFunction@" -> runSMGaugeCouplingsFunction,
"@setSMStrongCoupling@" -> IndentText[setSMStrongCoupling],
"@applyLowScaleConstraint@" -> IndentText[WrapLines[applyLowScaleConstraint]],
"@setDRbarUpQuarkYukawaCouplings@" -> IndentText[WrapLines[setDRbarYukawaCouplings[[1]]]],
"@setDRbarDownQuarkYukawaCouplings@" -> IndentText[WrapLines[setDRbarYukawaCouplings[[2]]]],
"@setDRbarElectronYukawaCouplings@" -> IndentText[WrapLines[setDRbarYukawaCouplings[[3]]]],
"@calculateScalarScalarLoopQCDFactor@" -> IndentText[WrapLines[calculateScalarScalarLoopQCDFactor]],
"@calculateScalarFermionLoopQCDFactor@" -> IndentText[WrapLines[calculateScalarFermionLoopQCDFactor]],
"@calculatePseudoscalarFermionLoopQCDFactor@" -> IndentText[WrapLines[calculatePseudoscalarFermionLoopQCDFactor]],
Expand Down
84 changes: 80 additions & 4 deletions templates/effective_couplings.cpp.in
Expand Up @@ -33,8 +33,9 @@ using namespace effective_couplings;
#define DERIVEDPARAMETER(parameter) model.##parameter()
#define PHASE(parameter) model.get_##parameter()
#define PHYSICAL(parameter) model.get_physical().parameter
#define MZDRbar sm.get_MVZ()
#define MWDRbar sm.get_MVWp()
#define MODEL model
#define MZDRbar sm->get_MVZ()
#define MWDRbar sm->get_MVWp()

@ModelName@_effective_couplings::@ModelName@_effective_couplings(
const @ModelName@_mass_eigenstates& model_,
Expand Down Expand Up @@ -67,8 +68,83 @@ void @ModelName@_effective_couplings::copy_mixing_matrices_from_model()
@copyMixingMatrices@
}

@runSMParametersFunction@
@runSMGaugeCouplingsFunction@
void @ModelName@_effective_couplings::run_SM_parameters_to(double m)
{
using namespace standard_model;

Standard_model sm;

sm.set_loops(2);
sm.set_thresholds(0);
sm.set_low_energy_data(qedqcd);
sm.set_physical_input(physical_input);

sm.initialise_from_input();
sm.run_to(m);

// ensure on-shell SM vev and top mass
sm.set_v(1.0 / Sqrt(qedqcd.displayFermiConstant() * Sqrt(2.0)));
sm.set_Yu(2, 2, -Sqrt(2.0) * qedqcd.displayPoleMt() / sm.get_v());
sm.calculate_DRbar_masses();

Low_scale_matching matching;
matching.model = &model;
matching.sm = &sm;
matching.match_model_to_SM();
}

void @ModelName@_effective_couplings::run_SM_strong_coupling_to(double m)
{
using namespace standard_model;

Standard_model sm;

sm.set_loops(2);
sm.set_thresholds(0);
sm.set_low_energy_data(qedqcd);
sm.set_physical_input(physical_input);

sm.initialise_from_input();
sm.run_to(m);

@setSMStrongCoupling@
}

void @ModelName@_effective_couplings::Low_scale_matching::match_model_to_SM()
{
@applyLowScaleConstraint@
}

void @ModelName@_effective_couplings::Low_scale_matching::set_@UpYukawa@_from_SM()
{
Eigen::Matrix<std::complex<double>,3,3> topDRbar(ZEROMATRIXCOMPLEX(3,3));
topDRbar(0,0) = sm->get_MFu(0);
topDRbar(1,1) = sm->get_MFu(1);
topDRbar(2,2) = sm->get_MFu(2);

@setDRbarUpQuarkYukawaCouplings@
}

void @ModelName@_effective_couplings::Low_scale_matching::set_@DownYukawa@_from_SM()
{
Eigen::Matrix<std::complex<double>,3,3> bottomDRbar(ZEROMATRIXCOMPLEX(3,3));
bottomDRbar(0,0) = sm->get_MFd(0);
bottomDRbar(1,1) = sm->get_MFd(1);
bottomDRbar(2,2) = sm->get_MFd(2);

@setDRbarDownQuarkYukawaCouplings@
}

void @ModelName@_effective_couplings::Low_scale_matching::set_@ElectronYukawa@_from_SM()
{
Eigen::Matrix<std::complex<double>,3,3> electronDRbar(ZEROMATRIXCOMPLEX(3,3));
electronDRbar(0,0) = sm->get_MFe(0);
electronDRbar(1,1) = sm->get_MFe(1);
electronDRbar(2,2) = sm->get_MFe(2);

@setDRbarElectronYukawaCouplings@
}

std::complex<double> @ModelName@_effective_couplings::scalar_scalar_qcd_factor(double m_decay, double m_loop) const
{
std::complex<double> result(1.0, 0.0);
Expand Down
19 changes: 17 additions & 2 deletions templates/effective_couplings.hpp.in
Expand Up @@ -30,6 +30,10 @@

namespace flexiblesusy {

namespace standard_model {
class Standard_model;
}

class @ModelName@_effective_couplings {
public:
@ModelName@_effective_couplings(const @ModelName@_mass_eigenstates&,
Expand All @@ -51,6 +55,16 @@ public:

@loopCouplingsPrototypes@
private:
struct Low_scale_matching {
@ModelName@_mass_eigenstates* model;
standard_model::Standard_model* sm;

void match_model_to_SM();
void set_@UpYukawa@_from_SM();
void set_@DownYukawa@_from_SM();
void set_@ElectronYukawa@_from_SM();
};

@ModelName@_mass_eigenstates model;
softsusy::QedQcd qedqcd;
Physical_input physical_input;
Expand All @@ -59,8 +73,9 @@ private:

void copy_mixing_matrices_from_model();

@runSMParametersPrototype@
@runSMGaugeCouplingsPrototype@
void run_SM_parameters_to(double m);
void run_SM_strong_coupling_to(double m);

// higher order corrections to the amplitudes for
// effective coupling to photons
std::complex<double> scalar_scalar_qcd_factor(double, double) const;
Expand Down

0 comments on commit ee58b39

Please sign in to comment.