source: codes/icosagcm/devel/src/dynamics/caldyn_gcm.F90 @ 827

Last change on this file since 827 was 827, checked in by dubos, 5 years ago

devel : towards Fortran driver for unstructured/LAM meshes

File size: 13.7 KB
RevLine 
[12]1MODULE caldyn_gcm_mod
[19]2  USE icosa
[151]3  USE transfert_mod
[731]4  USE caldyn_vars_mod
[529]5  USE caldyn_kernels_hevi_mod
[362]6  USE caldyn_kernels_base_mod
[361]7  USE caldyn_kernels_mod
[586]8  USE omp_para
9  USE mpipara
[350]10  IMPLICIT NONE
[132]11  PRIVATE
12
[362]13  PUBLIC init_caldyn, caldyn_BC, caldyn
14 
[12]15CONTAINS
[15]16 
[98]17  SUBROUTINE init_caldyn
[827]18    USE compute_mod, ONLY : compute_pvort_only
19    USE compute_pvort_only_mod, ONLY : compute_pvort_only_hex
20
[122]21    CHARACTER(len=255) :: def
[179]22    INTEGER            :: ind
23    REAL(rstd),POINTER :: planetvel(:)
[534]24
25    hydrostatic=.TRUE.
26    CALL getin("hydrostatic",hydrostatic)
[122]27 
[572]28    dysl=.NOT.hydrostatic ! dysl defaults to .FALSE. if hydrostatic, .TRUE. if NH                                             
29    CALL getin("dysl",dysl)
30    dysl_geopot=dysl
31    CALL getin("dysl_geopot",dysl_geopot)
32    dysl_caldyn_fast=dysl
33    CALL getin("dysl_caldyn_fast",dysl_caldyn_fast)
34    dysl_slow_hydro=dysl
35    CALL getin("dysl_slow_hydro",dysl_slow_hydro)
36    dysl_pvort_only=dysl
37    CALL getin("dysl_pvort_only",dysl_pvort_only)
38    dysl_caldyn_coriolis=dysl
39    CALL getin("dysl_caldyn_coriolis",dysl_caldyn_coriolis)
[624]40    dysl_caldyn_vert=dysl
41    CALL getin("dysl_caldyn_vert",dysl_caldyn_vert)
[572]42
[628]43    def='advective'
44    CALL getin('caldyn_vert',def)
45    SELECT CASE(TRIM(def))
46    CASE('advective')
47       caldyn_vert_variant=caldyn_vert_noncons
48    CASE('conservative')
49       IF(.NOT. dysl_caldyn_vert) THEN
50          IF (is_mpi_root) PRINT *,'caldyn_vert=cons requires dysl_caldyn_vert=.TRUE.'
51          STOP
52       END IF
53       caldyn_vert_variant=caldyn_vert_cons
54    CASE DEFAULT
55       IF (is_mpi_root) PRINT *,'Bad selector for variable caldyn_vert : <', &
56            TRIM(def),'> options are <conservative>, <advective>'
57       STOP
58    END SELECT
59    IF (is_master) PRINT *, 'caldyn_vert=',def
60   
[195]61    def='energy'
[125]62    CALL getin('caldyn_conserv',def)
63    SELECT CASE(TRIM(def))
64    CASE('energy')
[733]65       caldyn_conserv=conserv_energy
[735]66    CASE('energy_gassmann')
67       caldyn_conserv=conserv_gassmann
[126]68    CASE('enstrophy')
[733]69       caldyn_conserv=conserv_enstrophy
[125]70    CASE DEFAULT
[159]71       IF (is_mpi_root) PRINT *,'Bad selector for variable caldyn_conserv : <', &
[735]72            TRIM(def),'> options are <energy>, <energy_gassmann>, <enstrophy>'
[125]73       STOP
74    END SELECT
[295]75    IF (is_master) PRINT *, 'caldyn_conserv=',def
[125]76
[733]77    def='trisk'
78    CALL getin('caldyn_kinetic',def)
79    SELECT CASE(TRIM(def))
80    CASE('trisk')
81       caldyn_kinetic=kinetic_trisk
82    CASE('consistent')
83       caldyn_kinetic=kinetic_consistent
84    CASE DEFAULT
85       IF (is_mpi_root) PRINT *,'Bad selector for variable caldyn_kinetic : <', &
86            TRIM(def),'> options are <trisk>, <consistent>'
87       STOP
88    END SELECT
89    IF (is_master) PRINT *, 'caldyn_kinetic=',def
90
[413]91    nqdyn=1 ! default value
[534]92    physics_thermo = thermo_none
[413]93
[401]94    def='theta'
[413]95    CALL getin('thermo',def)
[401]96    SELECT CASE(TRIM(def))
[534]97    CASE('boussinesq')
98       boussinesq=.TRUE.
99       caldyn_thermo=thermo_boussinesq
100       IF(.NOT. hydrostatic) THEN
101          PRINT *, 'thermo=boussinesq and hydrostatic=.FALSE. : Non-hydrostatic boussinesq equations are not supported'
102          STOP
103       END IF
[401]104    CASE('theta')
105       caldyn_thermo=thermo_theta
[406]106       physics_thermo=thermo_dry
[401]107    CASE('entropy')
108       caldyn_thermo=thermo_entropy
[406]109       physics_thermo=thermo_dry
110    CASE('theta_fake_moist')
111       caldyn_thermo=thermo_theta
112       physics_thermo=thermo_fake_moist
113    CASE('entropy_fake_moist')
114       caldyn_thermo=thermo_entropy
115       physics_thermo=thermo_fake_moist
116    CASE('moist')
[413]117       caldyn_thermo=thermo_moist_debug
[406]118       physics_thermo=thermo_moist
[413]119       nqdyn = 2
[401]120    CASE DEFAULT
121       IF (is_mpi_root) PRINT *,'Bad selector for variable caldyn_thermo : <', &
122            TRIM(def),'> options are <theta>, <entropy>'
123       STOP
124    END SELECT
[413]125
126    IF(is_master) THEN
127       SELECT CASE(caldyn_thermo)
128       CASE(thermo_theta)
129          PRINT *, 'caldyn_thermo = thermo_theta'
130       CASE(thermo_entropy)
131          PRINT *, 'caldyn_thermo = thermo_entropy'
132       CASE(thermo_moist_debug)
133          PRINT *, 'caldyn_thermo = thermo_moist_debug'
134       CASE DEFAULT
135          STOP
136       END SELECT
137
138       SELECT CASE(physics_thermo)
139       CASE(thermo_dry)
140          PRINT *, 'physics_thermo = thermo_dry'
141       CASE(thermo_fake_moist)
142          PRINT *, 'physics_thermo = thermo_fake_moist'
143       CASE(thermo_moist)
144          PRINT *, 'physics_thermo = thermo_moist'
145       END SELECT
146
147       PRINT *, 'nqdyn =', nqdyn
148    END IF
149
[17]150    CALL allocate_caldyn
[179]151
152    DO ind=1,ndomain
[202]153       IF (.NOT. assigned_domain(ind)) CYCLE
[179]154       CALL swap_dimensions(ind)
155       CALL swap_geometry(ind)
156       planetvel=f_planetvel(ind)
157       CALL compute_planetvel(planetvel)
158    END DO
159
[827]160    compute_pvort_only => compute_pvort_only_hex
161
[15]162  END SUBROUTINE init_caldyn
[179]163
[12]164  SUBROUTINE allocate_caldyn
[735]165    CALL allocate_field(f_qu,field_u,type_real,llm, name='qu')
166    CALL allocate_field(f_qv,field_z,type_real,llm, name='qv')
167    CALL allocate_field(f_Kv,field_z,type_real,llm, name='Kv')
168    CALL allocate_field(f_hv,field_z,type_real,llm, name='hv')
[159]169    CALL allocate_field(f_pk,    field_t,type_real,llm,  name='pk')
[735]170    CALL allocate_field(f_wwuu,  field_u,type_real,llm+1,name='wwuu')
[179]171    CALL allocate_field(f_planetvel,  field_u,type_real, name='planetvel') ! planetary velocity at r=a
[558]172    IF(.NOT.hydrostatic) THEN
173       CALL allocate_field(f_Fel,      field_u,type_real,llm+1,name='F_el')
174       CALL allocate_field(f_gradPhi2, field_t,type_real,llm+1,name='gradPhi2')
175       CALL allocate_field(f_wil,      field_t,type_real,llm+1,name='w_il')
176       CALL allocate_field(f_Wetadot,  field_t,type_real,llm,name='W_etadot')
177    END IF
[12]178  END SUBROUTINE allocate_caldyn
[157]179
[350]180  SUBROUTINE caldyn_BC(f_phis, f_geopot, f_wflux)
[157]181    TYPE(t_field),POINTER :: f_phis(:)
[350]182    TYPE(t_field),POINTER :: f_geopot(:)
[157]183    TYPE(t_field),POINTER :: f_wflux(:)
184    REAL(rstd),POINTER  :: phis(:)
185    REAL(rstd),POINTER  :: wflux(:,:)
186    REAL(rstd),POINTER  :: geopot(:,:)
187    REAL(rstd),POINTER  :: wwuu(:,:)
188
189    INTEGER :: ind,i,j,ij,l
190
[295]191    IF (is_omp_first_level) THEN
[157]192       DO ind=1,ndomain
[186]193          IF (.NOT. assigned_domain(ind)) CYCLE
[157]194          CALL swap_dimensions(ind)
195          CALL swap_geometry(ind)
196          geopot=f_geopot(ind)
197          phis=f_phis(ind)
198          wflux=f_wflux(ind)
199          wwuu=f_wwuu(ind)
200         
[174]201          DO ij=ij_begin_ext,ij_end_ext
202              ! lower BCs : geopot=phis, wflux=0, wwuu=0
203              geopot(ij,1) = phis(ij)
204              wflux(ij,1) = 0.
205              wwuu(ij+u_right,1)=0   
206              wwuu(ij+u_lup,1)=0   
207              wwuu(ij+u_ldown,1)=0
208              ! top BCs : wflux=0, wwuu=0
209              wflux(ij,llm+1)  = 0.
210              wwuu(ij+u_right,llm+1)=0   
211              wwuu(ij+u_lup,llm+1)=0   
212              wwuu(ij+u_ldown,llm+1)=0
[157]213          ENDDO
214       END DO
215    ENDIF
216
[295]217    !$OMP BARRIER
[157]218  END SUBROUTINE caldyn_BC
[56]219   
[159]220  SUBROUTINE caldyn(write_out,f_phis, f_ps, f_mass, f_theta_rhodz, f_u, f_q, &
[350]221       f_geopot, f_hflux, f_wflux, f_dps, f_dmass, f_dtheta_rhodz, f_du)
[354]222    USE observable_mod
[167]223    USE disvert_mod, ONLY : caldyn_eta, eta_mass
[145]224    USE trace
[129]225    LOGICAL,INTENT(IN)    :: write_out
[126]226    TYPE(t_field),POINTER :: f_phis(:)
[12]227    TYPE(t_field),POINTER :: f_ps(:)
[159]228    TYPE(t_field),POINTER :: f_mass(:)
[126]229    TYPE(t_field),POINTER :: f_theta_rhodz(:)
230    TYPE(t_field),POINTER :: f_u(:)
231    TYPE(t_field),POINTER :: f_q(:)
[350]232    TYPE(t_field),POINTER :: f_geopot(:)
[134]233    TYPE(t_field),POINTER :: f_hflux(:), f_wflux(:)
[360]234    TYPE(t_field) :: f_dps(:)
235    TYPE(t_field) :: f_dmass(:)
236    TYPE(t_field) :: f_dtheta_rhodz(:)
237    TYPE(t_field) :: f_du(:)
[12]238   
[159]239    REAL(rstd),POINTER :: ps(:), dps(:)
[387]240    REAL(rstd),POINTER :: mass(:,:), theta_rhodz(:,:,:), dtheta_rhodz(:,:,:)
[134]241    REAL(rstd),POINTER :: u(:,:), du(:,:), hflux(:,:), wflux(:,:)
[159]242    REAL(rstd),POINTER :: qu(:,:)
[162]243    REAL(rstd),POINTER :: qv(:,:)
[151]244
245! temporary shared variable
[529]246    REAL(rstd),POINTER  :: theta(:,:,:) 
[157]247    REAL(rstd),POINTER  :: pk(:,:)
[156]248    REAL(rstd),POINTER  :: geopot(:,:)
[162]249    REAL(rstd),POINTER  :: convm(:,:) 
[151]250    REAL(rstd),POINTER  :: wwuu(:,:)
[157]251       
252    INTEGER :: ind
[151]253    LOGICAL,SAVE :: first=.TRUE.
254!$OMP THREADPRIVATE(first)
[12]255   
[162]256    IF (first) THEN
[151]257      first=.FALSE.
[162]258      IF(caldyn_eta==eta_mass) THEN
259         CALL init_message(f_ps,req_i1,req_ps)
[190]260      ELSE
[162]261         CALL init_message(f_mass,req_i1,req_mass)
262      END IF
[151]263      CALL init_message(f_theta_rhodz,req_i1,req_theta_rhodz)
264      CALL init_message(f_u,req_e1_vect,req_u)
265      CALL init_message(f_qu,req_e1_scal,req_qu)
[361]266      ! Overlapping com/compute (deactivated) : MPI messages need to be sent at first call to caldyn
267      ! This is needed only once : the next ones will be sent by timeloop
[186]268!      IF(caldyn_eta==eta_mass) THEN
269!         CALL send_message(f_ps,req_ps)
270!         CALL wait_message(req_ps) 
271!      ELSE
272!         CALL send_message(f_mass,req_mass)
273!         CALL wait_message(req_mass) 
274!      END IF
275    ENDIF
276   
277    CALL trace_start("caldyn")
278
[361]279    IF(caldyn_eta==eta_mass) THEN
280       CALL send_message(f_ps,req_ps) ! COM00
[529]281       CALL wait_message(req_ps) ! COM00
[361]282    ELSE
283       CALL send_message(f_mass,req_mass) ! COM00
[529]284       CALL wait_message(req_mass) ! COM00
[361]285    END IF
286   
287    CALL send_message(f_theta_rhodz,req_theta_rhodz) ! COM01
[529]288    CALL wait_message(req_theta_rhodz) ! COM01 Moved from caldyn_pvort
[361]289    CALL send_message(f_u,req_u) ! COM02
[529]290    CALL wait_message(req_u) ! COM02
[126]291
[529]292    IF(.NOT.hydrostatic) THEN
293       STOP 'caldyn_gcm may not be used yet when non-hydrostatic'
294    END IF
295
[126]296    SELECT CASE(caldyn_conserv)
[733]297    CASE(conserv_energy) ! energy-conserving
[128]298       DO ind=1,ndomain
[186]299          IF (.NOT. assigned_domain(ind)) CYCLE
[128]300          CALL swap_dimensions(ind)
301          CALL swap_geometry(ind)
302          ps=f_ps(ind)
[157]303          u=f_u(ind)
304          theta_rhodz = f_theta_rhodz(ind)
[159]305          mass=f_mass(ind)
[157]306          theta = f_theta(ind)
[128]307          qu=f_qu(ind)
[162]308          qv=f_qv(ind)
[529]309          pk = f_pk(ind)
310          geopot = f_geopot(ind) 
311          hflux=f_hflux(ind)
312          convm = f_dmass(ind)
313          dtheta_rhodz=f_dtheta_rhodz(ind)
314          du=f_du(ind)
[387]315          CALL compute_pvort(ps,u,theta_rhodz(:,:,1), mass,theta,qu,qv) ! COM00 COM01 COM02
[529]316!          CALL compute_theta(ps,theta_rhodz, mass,theta)
317!          CALL compute_pvort_only(u,mass,qu,qv)
[128]318
[529]319          CALL compute_geopot(mass,theta, ps,pk,geopot)
320!          du(:,:)=0.
321!          CALL compute_caldyn_fast(0.,u,mass,theta,pk,geopot,du)
322       ENDDO       
[128]323
[529]324       CALL send_message(f_u,req_u) ! COM02
325       CALL wait_message(req_u) ! COM02
326       CALL send_message(f_qu,req_qu) ! COM03
327       CALL wait_message(req_qu) ! COM03
328
[128]329       DO ind=1,ndomain
[186]330          IF (.NOT. assigned_domain(ind)) CYCLE
[128]331          CALL swap_dimensions(ind)
332          CALL swap_geometry(ind)
333          ps=f_ps(ind)
[157]334          u=f_u(ind)
[529]335          theta_rhodz = f_theta_rhodz(ind)
[159]336          mass=f_mass(ind)
[157]337          theta = f_theta(ind)
[128]338          qu=f_qu(ind)
[529]339          qv=f_qv(ind)
[151]340          pk = f_pk(ind)
[156]341          geopot = f_geopot(ind) 
[157]342          hflux=f_hflux(ind)
[162]343          convm = f_dmass(ind)
[157]344          dtheta_rhodz=f_dtheta_rhodz(ind)
345          du=f_du(ind)
[529]346
[387]347          CALL compute_caldyn_horiz(u,mass,qu,theta,pk,geopot, hflux,convm,dtheta_rhodz(:,:,1),du)
[529]348!          CALL compute_caldyn_slow_hydro(u,mass,hflux,du, .FALSE.) ! FIXME
349!          CALL compute_caldyn_Coriolis(hflux,theta,qu, convm,dtheta_rhodz,du)
[162]350          IF(caldyn_eta==eta_mass) THEN
351             wflux=f_wflux(ind)
352             wwuu=f_wwuu(ind)
353             dps=f_dps(ind)
[387]354             CALL compute_caldyn_vert(u,theta,mass,convm, wflux,wwuu, dps, dtheta_rhodz(:,:,1), du)
[162]355          END IF
[128]356       ENDDO       
[347]357   
[733]358    CASE(conserv_enstrophy) ! enstrophy-conserving
[126]359       DO ind=1,ndomain
[186]360          IF (.NOT. assigned_domain(ind)) CYCLE
[126]361          CALL swap_dimensions(ind)
362          CALL swap_geometry(ind)
[157]363          ps=f_ps(ind)
364          u=f_u(ind)
365          theta_rhodz=f_theta_rhodz(ind)
[159]366          mass=f_mass(ind)
[157]367          theta = f_theta(ind)
368          qu=f_qu(ind)
[182]369          qv=f_qv(ind)
[387]370          CALL compute_pvort(ps,u,theta_rhodz(:,:,1), mass,theta,qu,qv)
[157]371          pk = f_pk(ind)
[156]372          geopot = f_geopot(ind) 
[183]373          CALL compute_geopot(ps,mass,theta, pk,geopot)
[134]374          hflux=f_hflux(ind)
[162]375          convm = f_dmass(ind)
[126]376          dtheta_rhodz=f_dtheta_rhodz(ind)
377          du=f_du(ind)
[387]378          CALL compute_caldyn_horiz(u,mass,qu,theta,pk,geopot, hflux,convm,dtheta_rhodz(:,:,1),du)
[162]379          IF(caldyn_eta==eta_mass) THEN
380             wflux=f_wflux(ind)
381             wwuu=f_wwuu(ind)
382             dps=f_dps(ind)
383             CALL compute_caldyn_vert(u,theta,mass,convm, wflux,wwuu, dps, dtheta_rhodz, du)
384          END IF
[126]385       ENDDO
386       
387    CASE DEFAULT
388       STOP
389    END SELECT
[12]390
[295]391!$OMP BARRIER
[126]392    !    CALL check_mass_conservation(f_ps,f_dps)
[145]393    CALL trace_end("caldyn")
[186]394!!$OMP BARRIER
[126]395   
396END SUBROUTINE caldyn
[179]397
[126]398!-------------------------------- Diagnostics ----------------------------
399
400  SUBROUTINE check_mass_conservation(f_ps,f_dps)
401    TYPE(t_field),POINTER :: f_ps(:)
402    TYPE(t_field),POINTER :: f_dps(:)
403    REAL(rstd),POINTER :: ps(:)
404    REAL(rstd),POINTER :: dps(:)
405    REAL(rstd) :: mass_tot,dmass_tot
406    INTEGER :: ind,i,j,ij
407   
408    mass_tot=0
409    dmass_tot=0
410   
411    CALL transfert_request(f_dps,req_i1)
412    CALL transfert_request(f_ps,req_i1)
413
414    DO ind=1,ndomain
415      CALL swap_dimensions(ind)
416      CALL swap_geometry(ind)
417
418      ps=f_ps(ind)
419      dps=f_dps(ind)
420
421      DO j=jj_begin,jj_end
422        DO i=ii_begin,ii_end
423          ij=(j-1)*iim+i
424          IF (domain(ind)%own(i,j)) THEN
425            mass_tot=mass_tot+ps(ij)*Ai(ij)/g
426            dmass_tot=dmass_tot+dps(ij)*Ai(ij)/g
427          ENDIF
428        ENDDO
429      ENDDO
430   
431    ENDDO
[131]432    IF (is_mpi_root) PRINT*, "mass_tot ", mass_tot,"      dmass_tot ",dmass_tot       
[126]433
434  END SUBROUTINE check_mass_conservation 
[12]435 
436END MODULE caldyn_gcm_mod
Note: See TracBrowser for help on using the repository browser.