aboutsummaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorjthorn <jthorn@e296648e-0e4f-0410-bd07-d597d9acff87>2002-06-16 18:54:25 +0000
committerjthorn <jthorn@e296648e-0e4f-0410-bd07-d597d9acff87>2002-06-16 18:54:25 +0000
commit1d20738d4e3fca049dcddadd12bddcba3b35a320 (patch)
tree774016089ecf404da0b1487180ba0112456c7799 /src
parentf7216a27e1388f70b04fe68c2bd43449d668f457 (diff)
[[This is a redo of my "cvs import" of 2002/06/11, this time using proper
cvs operations (commit/delete/add) to preserve the full CVS history of this thorn.]] This is a major cleanup/revision of AEIThorns/Exact. Major user-visible changes: * major expansion of doc/documentation.tex * major expansion of documentation in param.ccl file * rename all parameters, systematize spacetime/coordinate/parameter names (there is a perl script in par/convert-pars.pl to convert old parameter files to the new names) * [from Mitica Vulcanov] many additions and fixes to cosmological solutions and Schwarzschild-Lemaitre * fix stress-energy tensor computations so they work -- before they were all disabled in CVS (INCLUDES lines were commented out in interface.ccl) due to requiring excessive friendship with evolution thorns and/or public parameters; new code copies parameters to restricted grid scalars, which Cactus automagically "pushes" to friends * added some more tests to testsuite, though these don't yet work fully Additional internal changes: * rename many Fortran subroutines (and a few C ones too) so their names start with the thorn name to reduce the chances of name collisions with other thorns * move all metrics to subdirectory so the main source directory isn't so cluttered * move two files containing subroutines which were never called (they didn't belong in this thorn, but somehow got into cvs by accident) into new archive/ directory * some (small) improvements in efficiency -- the exact_model parameter is now decoded from a keyword (string) to an integer once at INITIAL, and that integer tested by the stress-energy tensor code, rather than requiring a separate series of string tests at each grid point (!) like the old stress-energy tensor code did Modified Files: Scalar_CalcTmunu.inc major rewrite * use integer tests of decoded_exact_model to select model instead of string tests of exact_model * add code from Mitica Vulcanov for many new models, also fix some bugs in existing models * since this code is compiled as part of evolution thorns, it can't see our parameters, so code now uses "___" protected grid scalar copies of our parameters -- see comments in ../../param.ccl for more on why we do this Scalar_CalcTmunu_temps.inc add a bunch of new temp variables used by the Scalar_CalcTmunu.inc code Added Files: param_defs.inc new Fortran 77/90 include file of #define constants for decoded string parameters (currently only decoded_exact_model) git-svn-id: http://svn.einsteintoolkit.org/cactus/EinsteinInitialData/Exact/trunk@102 e296648e-0e4f-0410-bd07-d597d9acff87
Diffstat (limited to 'src')
-rw-r--r--src/include/Scalar_CalcTmunu.inc409
-rw-r--r--src/include/Scalar_CalcTmunu_temps.inc11
-rw-r--r--src/include/param_defs.inc66
3 files changed, 406 insertions, 80 deletions
diff --git a/src/include/Scalar_CalcTmunu.inc b/src/include/Scalar_CalcTmunu.inc
index 99c3146..5bb7cbf 100644
--- a/src/include/Scalar_CalcTmunu.inc
+++ b/src/include/Scalar_CalcTmunu.inc
@@ -3,80 +3,335 @@ C you can find in "src" directory through the components of the
C stress-eergy tensor. Being different in specific cases it is
C necessary to check first which metric is running.
C Author : Dumitru Vulcanov (Timisoara, Romania)
-
-
-C Kasner like metric
-
- if (CCTK_Equals(exactmodel,"kasner").eq.1) then
-
- Ttt = Ttt - kasner_q*(2-3*kasner_q)/(CCTK_time**2)
-
-C DeSitter metric
-
- elseif (CCTK_Equals(exactmodel,"desitter").eq.1) then
-
- Ttt = Ttt - desitt_b/(CCTK_time**2)
-
-C Robertson Walker cosmology
-
- elseif (CCTK_Equals(exactmodel,"rob-wal").eq.1) then
-
- rr2 = x(i,j,k)**2+y(i,j,k)**2+z(i,j,k)**2
- aha = desitt_b/(3*desitt_a**2*CCTK_time**2)
-
- Ttt = Ttt + desitt_b/(CCTK_time**2)/(desitt_a**4)
-
- Txx = Txx + 1.d0+ (aha - 1.d0)*x(i,j,k)**2/rr2
-
- Tyy = Tyy + 1.d0+ (aha - 1.d0)*y(i,j,k)**2/rr2
-
- Tzz = Tzz + 1.d0+ (aha - 1.d0)*z(i,j,k)**2/rr2
-
- Txy = Txy + (aha-1.d0)*x(i,j,k)*y(i,j,k)/rr2
-
- Txz = Txz + (aha-1.d0)*x(i,j,k)*z(i,j,k)/rr2
-
- Tyz = Tyz + (aha-1.d0)*y(i,j,k)*z(i,j,k)/rr2
-
-C Schwarzschild static star
-
- elseif (CCTK_Equals(exactmodel,"starschwarz").eq.1) then
-
- rr = dsqrt(x(i,j,k)**2+y(i,j,k)**2+z(i,j,k)**2)
-
- if (rr.le.starschwarz_r) then
-
-
- sum = gxx(i,j,k)*betax(i,j,k)**2+gxx(i,j,k)*betay(i,j,k)**2 +
- & gzz(i,j,k)*betaz(i,j,k)**2 +
- & 2*gxy(i,j,k)*betax(i,j,k)*betay(i,j,k) +
- & 2*gxz(i,j,k)*betax(i,j,k)*betaz(i,j,k) +
- & 2*gyz(i,j,k)*betay(i,j,k)*betaz(i,j,k)
- & -alp(i,j,k)**2
-
-
- unu = 3*starschwarz_m/(4*pi*starschwarz_m**3)
-
- doi = dsqrt(1-2*starschwarz_m/starschwarz_r)
-
- trei= dsqrt(1-2*starschwarz_m*rr**2/(starschwarz_r**3))
-
- Ttt = Ttt +unu*alp(i,j,k)**2 - (unu*(3*doi/2-trei/2)**2)*sum
-
- Txx = Txx - (unu*(doi-trei)/(trei-3*unu))*gxx(i,j,k)
-
- Tyy = Tyy - (unu*(doi-trei)/(trei-3*unu))*gyy(i,j,k)
-
- Tzz = Tzz - (unu*(doi-trei)/(trei-3*unu))*gzz(i,j,k)
-
-
- else
- Ttt = Ttt
- Txx = Txx
- Tyy = Tyy
- Tzz = Tzz
-
- end if
-
-
- end if \ No newline at end of file
+C $Header$
+
+C Varianta cu un singur param. (raza initiala) pt Rob-Walker
+
+#include "param_defs.inc"
+
+c
+c FIXME:
+c If we could be certain that this code were always compiled as Fortran 90,
+c the decode here could be done with a case statement, which ought to give
+c better performance than the if-else chain we use now. But in practice
+c Cactus has enough other overheads that this is not bothering with...
+c
+
+c
+c ***** KLUDGE *****
+c
+c This code is #include-d into various evolution thorns, and alas does not
+c have direct access to thorn Exact parameters. Instead, this code must
+c use the restricted-grid-scalar copies of the parameters. In practice,
+c this means changing "__" to "___" in all parameter names (but not in the
+c #define constants in "param_defs.inc"). See the comments in param.ccl
+c for further information on this.
+c
+
+cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
+ccccc Minkowski spacetime cccccccccccccccccccccccccccccccccccccccccccccccccccccc
+cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
+
+ if (decoded_exact_model .eq. EXACT__Minkowski) then
+c no stress-energy tensor in this model
+ elseif (decoded_exact_model .eq. EXACT__Minkowski_shift) then
+c no stress-energy tensor in this model
+ elseif (decoded_exact_model .eq. EXACT__Minkowski_funny) then
+c no stress-energy tensor in this model
+ elseif (decoded_exact_model .eq. EXACT__Minkowski_gauge_wave) then
+c no stress-energy tensor in this model
+
+cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
+ccccc black hole spacetimes cccccccccccccccccccccccccccccccccccccccccccccccccccc
+cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
+
+ elseif (decoded_exact_model .eq. EXACT__Schwarzschild_EF) then
+c no stress-energy tensor in this model
+ elseif (decoded_exact_model .eq. EXACT__Schwarzschild_PG) then
+c no stress-energy tensor in this model
+ elseif (decoded_exact_model .eq. EXACT__Schwarzschild_Novikov) then
+c no stress-energy tensor in this model
+ elseif (decoded_exact_model .eq. EXACT__Kerr_BoyerLindquist) then
+c no stress-energy tensor in this model
+ elseif (decoded_exact_model .eq. EXACT__Kerr_KerrSchild) then
+c no stress-energy tensor in this model
+
+cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
+
+c
+c Schwarzschild-Lemaitre spacetime
+c (Schwarzschild black hole with cosmological constant)
+c
+ elseif (decoded_exact_model .eq. EXACT__Schwarzschild_Lemaitre) then
+ razsch2=x(i,j,k)*x(i,j,k)+y(i,j,k)*y(i,j,k)+z(i,j,k)*z(i,j,k)
+ coefsch=-Schwarzschild_Lemaitre___Lambda/(8.0D0*pi)
+ pppsch=1.0D0-2.0D0*Schwarzschild_Lemaitre___mass/sqrt(razsch2)
+ & -Schwarzschild_Lemaitre___Lambda*razsch2/3.0D0
+ unusch=(1.0D0-pppsch)/pppsch/razsch2
+
+ Ttt = Ttt-coefsch*pppsch
+ Ttx = Ttx
+ Tty = Tty
+ Ttz = Ttz
+ Txx = Txx+coefsch*(1.0D0+x(i,j,k)*x(i,j,k)*unusch)
+ Tyy = Tyy+coefsch*(1.0D0+y(i,j,k)*y(i,j,k)*unusch)
+ Tzz = Tzz+coefsch*(1.0D0+z(i,j,k)*z(i,j,k)*unusch)
+ Txy = Txy+coefsch*x(i,j,k)*y(i,j,k)*unusch
+ Txz = Txz+coefsch*x(i,j,k)*z(i,j,k)*unusch
+ Tyz = Tyz+coefsch*y(i,j,k)*z(i,j,k)*unusch
+
+cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
+
+ elseif (decoded_exact_model .eq. EXACT__multi_BH) then
+c no stress-energy tensor in this model
+ elseif (decoded_exact_model .eq. EXACT__Alvi) then
+c no stress-energy tensor in this model
+ elseif (decoded_exact_model .eq. EXACT__Thorne_fakebinary) then
+c no stress-energy tensor in this model
+
+cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
+ccccc cosmological spacetimes cccccccccccccccccccccccccccccccccccccccccccccccccc
+cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
+
+c
+c Lemaitre spacetime
+c
+ elseif (decoded_exact_model .eq. EXACT__Lemaitre) then
+ unu1 = sqrt(3.0D0*Lemaitre___Lambda)
+ & * CCTK_time * (Lemaitre___kappa+1.0D0) / (2.0D0)
+ raz = Lemaitre___R0*(cosh(unu1)
+ & + sqrt(1.0D0+8.0D0*pi*Lemaitre___epsilon0
+ & /Lemaitre___Lambda)
+ & *sinh(unu1))
+ & **(2.0D0/(3.0D0*Lemaitre___kappa+3.0D0))
+ raz2 = raz*raz
+ treiori = -Lemaitre___Lambda*raz2/8.0D0/pi
+ & +Lemaitre___epsilon0*Lemaitre___kappa
+ & *raz**(-3.0D0*Lemaitre___kappa-1.0D0)
+
+ Ttt = Ttt + Lemaitre___Lambda/8.0D0/pi
+ & + Lemaitre___epsilon0*raz**(-3.0D0*(Lemaitre___kappa+1.0D0))
+ Txx = Txx + treiori
+ Tyy = Tyy + treiori
+ Tzz = Tzz + treiori
+ Txy = Txy
+ Tyz = Tyz
+ Txz = Txz
+
+cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
+
+c
+c Robertson-Walker spacetime
+C
+ elseif (decoded_exact_model .eq. EXACT__Robertson_Walker) then
+ rr2 = x(i,j,k)*x(i,j,k)+y(i,j,k)*y(i,j,k)+z(i,j,k)*z(i,j,k)
+
+ if (Robertson_Walker___pressure .gt. 0) then
+ aha1 = Robertson_Walker___k * (Robertson_Walker___R0**2)
+ & / (8.0D0*pi*(raza(i,j,k)**2))
+ aha2 = Robertson_Walker___k/(1.0D0 - Robertson_Walker___k*rr2)
+
+ Ttt = Ttt + 3.0D0*aha1/(raza(i,j,k)*raza(i,j,k))
+ Txx = Txx + aha1*(1.0D0 + aha2*x(i,j,k)*x(i,j,k))
+ Tyy = Tyy + aha1*(1.0D0 + aha2*y(i,j,k)*y(i,j,k))
+ Tzz = Tzz + aha1*(1.0D0 + aha2*z(i,j,k)*z(i,j,k))
+ Txy = Txy + aha1*aha2*x(i,j,k)*y(i,j,k)
+ Txz = Txz + aha1*aha2*x(i,j,k)*z(i,j,k)
+ Tyz = Tyz + aha1*aha2*y(i,j,k)*y(i,j,k)
+ else
+ Ttt = Ttt+Robertson_Walker___rho * (Robertson_Walker___R0**3)
+ & / (raza(i,j,k)**3)
+ Txx = Txx
+ Tyy = Tyy
+ Tzz = Tzz
+ Txy = Txy
+ Txz = Txz
+ Tyz = Tyz
+ endif
+
+cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
+
+c
+c de Sitter spacetime
+c
+ elseif (decoded_exact_model .eq. EXACT__de_Sitter) then
+ Ttt = Ttt + 1.0D0/6.0D0/pi/(CCTK_time**2)
+ Ttx = Ttx
+ Tty = Tty
+ Ttz = Ttz
+ Txx = Txx
+ Tyy = Tyy
+ Tzz = Tzz
+ Txy = Txy
+ Txz = Txz
+ Tyz = Tyz
+
+cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
+
+c
+c de Sitter spacetime with cosmological constant
+c
+ elseif (decoded_exact_model .eq. EXACT__de_Sitter_Lambda) then
+ aaaa = de_Sitter_Lambda___scale/(8.0D0*pi)
+ bbbb = aaaa*exp(2.0D0*sqrt(de_Sitter_Lambda___scale/3.0D0)*CCTK_time)
+
+ Ttt = Ttt + aaaa
+ Ttx = Ttx
+ Tty = Tty
+ Ttz = Ttz
+ Txx = Txx - bbbb
+ Tyy = Tyy - bbbb
+ Tzz = Tzz - bbbb
+ Txy = Txy
+ Txz = Txz
+ Tyz = Tyz
+
+cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
+
+c
+c anti-de Sitter spacetime with cosmological constant
+c
+
+ elseif (decoded_exact_model .eq. EXACT__anti_de_Sitter_Lambda) then
+ aaaa1 = anti_de_Sitter_Lambda___scale/(8.0D0*pi)
+ bbbb1 = aaaa1*exp(2.0D0*sqrt(-anti_de_Sitter_Lambda___scale/3.0D0)
+ & *x(i,j,k))
+
+ Ttt = Ttt + bbbb1
+ Ttx = Ttx
+ Tty = Tty
+ Ttz = Ttz
+ Txx = Txx - aaaa1
+ Tyy = Tyy - bbbb1
+ Tzz = Tzz - bbbb1
+ Txy = Txy
+ Txz = Txz
+ Tyz = Tyz
+
+cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
+
+ elseif (decoded_exact_model .eq. EXACT__Bianchi_I) then
+c no stress-energy tensor in this model
+ elseif (decoded_exact_model .eq. EXACT__Goedel) then
+c no stress-energy tensor in this model
+
+cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
+
+c
+c Bertotti spacetime
+c
+ elseif (decoded_exact_model .eq. EXACT__Bertotti) then
+ bass = Bertotti___Lambda/(8.0D0*pi)
+ term1 = bass*exp(2.0D0*sqrt(-Bertotti___Lambda)*x(i,j,k))
+ term2 = bass*exp(2.0D0*sqrt(-Bertotti___Lambda)*z(i,j,k))
+
+ Ttt = Ttt + term1
+ Ttx = Ttx
+ Tty = Tty
+ Ttz = Ttz
+ Txx = Txx - bass
+ Tyy = Tyy - term2
+ Tzz = Tzz - bass
+ Txy = Txy
+ Txz = Txz
+ Tyz = Tyz
+
+cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
+
+c
+c Kasner-like spacetime
+c
+ elseif (decoded_exact_model .eq. EXACT__Kasner_like) then
+
+ kkkk=Kasner_like___q*(2.0D0-3.0D0*Kasner_like___q)
+ & /(8.0D0*pi*(CCTK_time**2))
+
+ Ttt = Ttt + kkkk
+ Ttx = Ttx
+ Tty = Tty
+ Ttz = Ttz
+ Txx = Txx + kkkk*CCTK_time**(2.0D0*Kasner_like___q)
+ Tyy = Tyy + kkkk*CCTK_time**(2.0D0*Kasner_like___q)
+ Tzz = Tzz + kkkk*CCTK_time**(2.0D0-4.0D0*Kasner_like___q)
+ Txy = Txy
+ Txz = Txz
+ Tyz = Tyz
+
+cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
+
+ elseif (decoded_exact_model .eq. EXACT__Kasner_axisymmetric) then
+c no stress-energy tensor in this model
+
+cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
+
+c
+c generalized Kasner spacetime
+c
+ elseif (decoded_exact_model .eq. EXACT__Kasner_generalized) then
+
+ kkkk1 = ( Kasner_generalized___p1 - Kasner_generalized___p1**2
+ & + Kasner_generalized___p2 - Kasner_generalized___p2**2
+ & - Kasner_generalized___p1*Kasner_generalized___p2 )
+ & / (8.0D0*pi*(CCTK_time**2))
+
+ Ttt = Ttt + kkkk1
+ Ttx = Ttx
+ Tty = Tty
+ Ttz = Ttz
+ Txx = Txx+kkkk1*CCTK_time**(2.0D0*Kasner_generalized___p1)
+ Tyy = Tyy+kkkk1*CCTK_time**(2.0D0*Kasner_generalized___p2)
+ Tzz = Tzz+kkkk1*CCTK_time**(2.0D0-2.0D0*Kasner_generalized___p1
+ & -2.0D0*Kasner_generalized___p2)
+ Txy = Txy
+ Txz = Txz
+ Tyz = Tyz
+
+cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
+
+ elseif (decoded_exact_model .eq. EXACT__Milne) then
+c no stress-energy tensor in this model
+
+cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
+ccccc miscellaneous spacetimes ccccccccccccccccccccccccccccccccccccccccccccccccc
+cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
+
+ elseif (decoded_exact_model .eq. EXACT__boost_rotation_symmetric) then
+c no stress-energy tensor in this model
+ elseif (decoded_exact_model .eq. EXACT__bowl) then
+c no stress-energy tensor in this model
+
+cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
+
+c
+c constant density star
+c
+ elseif (decoded_exact_model .eq. EXACT__constant_density_star) then
+ rr = sqrt(x(i,j,k)*x(i,j,k)+y(i,j,k)*y(i,j,k)+
+ & z(i,j,k)*z(i,j,k))
+ star_m = constant_density_star___mass
+ star_r = constant_density_star___radius
+
+ r3 = star_r**3
+ if (rr.le.star_r) then
+ unu = 3.0D0*sqrt(1.0D0-2.0D0*star_m/star_r)
+ doi = sqrt(1.0D0-2.0D0*star_m*rr*rr/r3)
+ trei= star_m*(unu-3.0D0*doi)/(2*pi*(unu-doi)*r3)
+ Ttt = Ttt + 3.0D0*star_m*
+ & (5.0D0-9.0D0*star_m/star_r - unu*doi
+ & -star_m*rr*rr/r3)/(8.0D0*pi*r3)
+ Txx = Txx -trei*(1.0D0+2.0D0*star_m*x(i,j,k)*x(i,j,k)/
+ & (doi*doi*r3))/2.0D0
+ Tyy = Tyy -trei*(1.0D0+2.0D0*star_m*y(i,j,k)*y(i,j,k)/
+ & (doi*doi*r3))/2.0D0
+ Tzz = Tzz -trei*(1.0D0+2.0D0*star_m*z(i,j,k)*z(i,j,k)/
+ & (doi*doi*r3))/2.0D0
+ Txy = Txy -trei*star_m*x(i,j,k)*y(i,j,k)/(doi*doi*r3)
+ Tyz = Tyz -trei*star_m*y(i,j,k)*z(i,j,k)/(doi*doi*r3)
+ Txz = Txz -trei*star_m*x(i,j,k)*z(i,j,k)/(doi*doi*r3)
+ endif
+
+cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
+
+ else
+ call CCTK_WARN(0,"Unknown value of Exact::decoded_exact_model")
+ endif
diff --git a/src/include/Scalar_CalcTmunu_temps.inc b/src/include/Scalar_CalcTmunu_temps.inc
index 684fcf3..2832e6b 100644
--- a/src/include/Scalar_CalcTmunu_temps.inc
+++ b/src/include/Scalar_CalcTmunu_temps.inc
@@ -1,3 +1,8 @@
-
- CCTK_REAL unu,doi,trei,rr,sum,rr2,aha
-
+c
+c temporary variables for code in "Scalar_CalcTmunu.inc"
+c
+ CCTK_REAL unu,doi,trei,rr,sum,rr2,aha1,aha2,kkkk,riih,rii2
+ CCTK_REAL aaaa,bbbb,aaaa1,bbbb1,kkkk1,r3,bass,term1,term2
+ CCTK_REAL unu1, raz, raz2, razsch2, coefsch, pppsch, unusch
+ CCTK_REAL treiori
+ CCTK_REAL star_m, star_r
diff --git a/src/include/param_defs.inc b/src/include/param_defs.inc
new file mode 100644
index 0000000..75d3e60
--- /dev/null
+++ b/src/include/param_defs.inc
@@ -0,0 +1,66 @@
+c decoded_exact_model.inc -- integer constants for decoded_exact_model
+c $Header$
+
+c
+c For reasons explained in our param.ccl file, we decode the exact_model
+c parameter, and all our other string-valued parameters used in computing
+c the stress-energy tensor, into integers. This file contains #define
+c definitions for those integers.
+c
+
+c
+c For each parameter, the value 0 is deliberately *not* a legal value
+c for the decoded integer, to help catch bugs where the decoded integer
+c is not initialized properly.
+c
+
+cccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccccc
+
+c
+c ***** definitions for decoded_exact_model *****
+c
+c These *MUST* be distinct integers, and there must be precisely one
+c definition for each value of exact_model in param.ccl . It is not
+c necessary that they be in numerical order, that is just to make things
+c look prettier.
+c
+c N.b. We are counting on the preprocessor being case-sensitive here,
+c since these same names with EXACT changed to Exact, are names
+c of subroutines for the individual metric types!
+c
+
+c Minkowski spacetime
+#define EXACT__Minkowski 1
+#define EXACT__Minkowski_shift 2
+#define EXACT__Minkowski_funny 3
+#define EXACT__Minkowski_gauge_wave 4
+
+c black hole spacetimes
+#define EXACT__Schwarzschild_EF 10
+#define EXACT__Schwarzschild_PG 11
+#define EXACT__Schwarzschild_Novikov 12
+#define EXACT__Kerr_BoyerLindquist 13
+#define EXACT__Kerr_KerrSchild 14
+#define EXACT__Schwarzschild_Lemaitre 15
+#define EXACT__multi_BH 16
+#define EXACT__Alvi 17
+#define EXACT__Thorne_fakebinary 18
+
+c cosmological spacetimes
+#define EXACT__Lemaitre 50
+#define EXACT__Robertson_Walker 51
+#define EXACT__de_Sitter 52
+#define EXACT__de_Sitter_Lambda 53
+#define EXACT__anti_de_Sitter_Lambda 54
+#define EXACT__Bianchi_I 55
+#define EXACT__Goedel 56
+#define EXACT__Bertotti 57
+#define EXACT__Kasner_like 58
+#define EXACT__Kasner_axisymmetric 59
+#define EXACT__Kasner_generalized 60
+#define EXACT__Milne 61
+
+c miscelaneous spacetimes
+#define EXACT__boost_rotation_symmetric 80
+#define EXACT__bowl 81
+#define EXACT__constant_density_star 82