source: trunk/LMDZ.MARS/libf/phymars/inistats.F @ 1917

Last change on this file since 1917 was 1621, checked in by emillour, 8 years ago

Further work on full dynamics/physics separation.

LMDZ.COMMON:

  • added phy_common/vertical_layers_mod.F90 to store information on vertical grid. This is where routines in the physics should get the information.
  • The contents of vertical_layers_mod intialized via dynphy_lonlat/inigeomphy_mod.F90.

LMDZ.MARS:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • created an "ini_tracer_mod" routine in module "tracer_mod" for a cleaner initialization of the later.
  • removed some purely dynamics-related outputs (etot0, zoom parameters, etc.) from diagfi.nc and stats.nc outputs as these informations are not available in the physics.

LMDZ.GENERIC:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • added nqtot to tracer_h.F90.
  • removed some purely dynamics-related outputs (etot0, zoom parameters, etc.) from diagfi.nc and stats.nc outputs as these informations are not available in the physics.

LMDZ.VENUS:

  • physics now completely decoupled from dynamics; the physics package may now be compiled as a library (-libphy option of makelmdz_fcm).
  • added infotrac_phy.F90 to store information on tracers in the physics. Initialized via iniphysiq.
  • added cpdet_phy_mod.F90 to store t2tpot etc. functions to be used in the physics. Initialized via iniphysiq. IMPORTANT: there are some hard-coded constants! These should match what is in cpdet_mod.F90 in the dynamics.
  • got rid of references to moyzon_mod module within the physics. The required variables (tmoy, plevmoy) are passed to the physics as arguments to physiq.

LMDZ.TITAN:

  • added infotrac_phy.F90 to store information on tracers in the physics. Initialized via iniphysiq.
  • added cpdet_phy_mod.F90 to store t2tpot etc. functions to be used in the physics.
  • Extra work required to completely decouple physics and dynamics: moyzon_mod should be cleaned up and information passed from dynamics to physics as as arguments. Likewise moyzon_ch and moyzon_mu should not be queried from logic_mod (which is in the dynamics).

EM

File size: 4.4 KB
Line 
1      subroutine inistats(ierr)
2
3      use statto_mod, only: istats,istime
4      use mod_phys_lmdz_para, only : is_master
5      USE vertical_layers_mod, ONLY: ap,bp,aps,bps,preff,
6     &                               pseudoalt,presnivs
7      USE nrtype, ONLY: pi
8      USE time_phylmdz_mod, ONLY: daysec,dtphys
9      USE regular_lonlat_mod, ONLY: lon_reg, lat_reg
10      USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, nbp_lev
11      implicit none
12
13      include "netcdf.inc"
14
15      integer,intent(out) :: ierr
16      integer :: nid
17      integer :: l,nsteppd
18      real, dimension(nbp_lev) ::  sig_s
19      real,allocatable :: lon_reg_ext(:) ! extended longitudes
20      integer :: idim_lat,idim_lon,idim_llm,idim_llmp1,idim_time
21      real, dimension(istime) :: lt
22      integer :: nvarid
23
24
25      IF (nbp_lon*nbp_lat==1) THEN
26        ! 1D model
27        ALLOCATE(lon_reg_ext(1))
28      ELSE
29        ! 3D model
30        ALLOCATE(lon_reg_ext(nbp_lon+1))
31      ENDIF
32     
33      write (*,*)
34      write (*,*) '                        || STATS ||'
35      write (*,*)
36      write (*,*) 'daysec',daysec
37      write (*,*) 'dtphys',dtphys
38      nsteppd=nint(daysec/dtphys)
39      write (*,*) 'nsteppd=',nsteppd
40      if (abs(float(nsteppd)-daysec/dtphys).gt.1.e-8*daysec)
41     &   stop'Dans Instat:  1jour .ne. n pas physiques'
42
43      if(mod(nsteppd,istime).ne.0)
44     &   stop'Dans Instat:  1jour .ne. n*istime pas physiques'
45
46      istats=nsteppd/istime
47      write (*,*) 'istats=',istats
48      write (*,*) 'Storing ',istime,'times per day'
49      write (*,*) 'thus every ',istats,'physical timestep '
50      write (*,*)
51
52      do l= 1, nbp_lev
53         sig_s(l)=((ap(l)+ap(l+1))/preff+bp(l)+bp(l+1))/2.
54         pseudoalt(l)=-10.*log(presnivs(l)/preff)   
55      enddo
56     
57      lon_reg_ext(1:nbp_lon)=lon_reg(1:nbp_lon)
58      IF (nbp_lon*nbp_lat/=1) THEN
59        ! In 3D, add extra redundant point (180 degrees,
60        ! since lon_reg starts at -180)
61        lon_reg_ext(nbp_lon+1)=-lon_reg_ext(1)
62      ENDIF
63
64      if (is_master) then
65      ! only the master needs do this
66
67      ierr = NF_CREATE("stats.nc",IOR(NF_CLOBBER,NF_64BIT_OFFSET),nid)
68      if (ierr.ne.NF_NOERR) then
69         write (*,*) NF_STRERROR(ierr)
70         stop ""
71      endif
72
73      ierr = NF_DEF_DIM (nid, "latitude", nbp_lat, idim_lat)
74      IF (nbp_lon*nbp_lat==1) THEN
75        ierr = NF_DEF_DIM (nid, "longitude", 1, idim_lon)
76      ELSE
77        ierr = NF_DEF_DIM (nid, "longitude", nbp_lon+1, idim_lon)
78      ENDIF
79      ierr = NF_DEF_DIM (nid, "altitude", nbp_lev, idim_llm)
80      ierr = NF_DEF_DIM (nid, "llmp1", nbp_lev+1, idim_llmp1)
81      ierr = NF_DEF_DIM (nid, "Time", NF_UNLIMITED, idim_time)
82
83      ierr = NF_ENDDEF(nid)
84      call def_var_stats(nid,"Time","Time",
85     &            "days since 0000-00-0 00:00:00",1,
86     &            idim_time,nvarid,ierr)
87! Time is initialised later by mkstats subroutine
88
89      call def_var_stats(nid,"latitude","latitude",
90     &            "degrees_north",1,idim_lat,nvarid,ierr)
91#ifdef NC_DOUBLE
92      ierr = NF_PUT_VAR_DOUBLE (nid,nvarid,lat_reg/pi*180)
93#else
94      ierr = NF_PUT_VAR_REAL (nid,nvarid,lat_reg/pi*180)
95#endif
96      call def_var_stats(nid,"longitude","East longitude",
97     &            "degrees_east",1,idim_lon,nvarid,ierr)
98#ifdef NC_DOUBLE
99      ierr = NF_PUT_VAR_DOUBLE (nid,nvarid,lon_reg_ext/pi*180)
100#else
101      ierr = NF_PUT_VAR_REAL (nid,nvarid,lon_reg_ext/pi*180)
102#endif
103
104! Niveaux verticaux, aps et bps
105      ierr = NF_REDEF (nid)
106#ifdef NC_DOUBLE
107      ierr = NF_DEF_VAR (nid,"altitude", NF_DOUBLE, 1,idim_llm,nvarid)
108#else
109      ierr = NF_DEF_VAR (nid,"altitude", NF_FLOAT, 1,idim_llm,nvarid)
110#endif
111      ierr = NF_PUT_ATT_TEXT (nid,nvarid,"long_name",8,"altitude")
112      ierr = NF_PUT_ATT_TEXT (nid,nvarid,'units',2,"km")
113      ierr = NF_PUT_ATT_TEXT (nid,nvarid,'positive',2,"up")
114      ierr = NF_ENDDEF(nid)
115#ifdef NC_DOUBLE
116      ierr = NF_PUT_VAR_DOUBLE (nid,nvarid,pseudoalt)
117#else
118      ierr = NF_PUT_VAR_REAL (nid,nvarid,pseudoalt)
119#endif
120      call def_var_stats(nid,"aps","hybrid pressure at midlayers"
121     & ," ",1,idim_llm,nvarid,ierr)
122#ifdef NC_DOUBLE
123      ierr = NF_PUT_VAR_DOUBLE (nid,nvarid,aps)
124#else
125      ierr = NF_PUT_VAR_REAL (nid,nvarid,aps)
126#endif
127
128      call def_var_stats(nid,"bps","hybrid sigma at midlayers"
129     & ," ",1,idim_llm,nvarid,ierr)
130#ifdef NC_DOUBLE
131      ierr = NF_PUT_VAR_DOUBLE (nid,nvarid,bps)
132#else
133      ierr = NF_PUT_VAR_REAL (nid,nvarid,bps)
134#endif
135
136      ierr=NF_CLOSE(nid)
137
138      endif ! of if (is_master)
139      end subroutine inistats
140
Note: See TracBrowser for help on using the repository browser.