MODULE physics_mod CHARACTER(LEN=255) :: physics_type="automatic" !$OMP THREADPRIVATE(physics_type) CONTAINS SUBROUTINE init_physics USE mpipara USE etat0_mod USE icosa USE physics_dcmip_mod,init_physics_dcmip=>init_physics ! USE physics_dry_mod IMPLICIT NONE physics_type='automatic' CALL getin("physics",physics_type) SELECT CASE(TRIM(physics_type)) CASE ('automatic') etat0_type='jablonowsky06' CALL getin("etat0",etat0_type) SELECT CASE(TRIM(etat0_type)) CASE('held_suarez') CASE DEFAULT IF(is_mpi_root) PRINT*,"NO PHYSICAL PACKAGE USED" END SELECT CASE ('dcmip') CALL init_physics_dcmip CASE ('dry') ! CALL init_physics_dry CASE DEFAULT PRINT*, 'init_physics : Bad selector for variable physics <',TRIM(physics_type), & '> options are , , ' STOP END SELECT END SUBROUTINE init_physics SUBROUTINE physics(it,jD_cur,jH_cur,f_phis, f_ps, f_theta_rhodz, f_ue, f_q) USE icosa ! USE physics_dry_mod USE physics_dcmip_mod, physics_dcmip=>physics USE etat0_mod USE etat0_heldsz_mod IMPLICIT NONE INTEGER, INTENT(IN) :: it REAL(rstd),INTENT(IN)::jD_cur,jH_cur TYPE(t_field),POINTER :: f_phis(:) TYPE(t_field),POINTER :: f_ps(:) TYPE(t_field),POINTER :: f_theta_rhodz(:) TYPE(t_field),POINTER :: f_ue(:) TYPE(t_field),POINTER :: f_q(:) LOGICAL:: firstcall,lastcall SELECT CASE(TRIM(physics_type)) CASE ('automatic') SELECT CASE(TRIM(etat0_type)) CASE('held_suarez') ! CALL transfert_request(f_ps,req_i1) ! CALL transfert_request(f_theta_rhodz,req_i1) ! CALL transfert_request(f_ue,req_e1_vect) CALL held_suarez(f_ps,f_theta_rhodz,f_ue) CASE DEFAULT ! PRINT*,"NO PHYSICAL PACAKAGE USED" ! FIXME MPI END SELECT CASE ('dcmip') CALL physics_dcmip(it, f_phis, f_ps, f_theta_rhodz, f_ue, f_q) CASE ('dry') ! CALL physics_dry(it,jD_cur,jH_cur,f_phis, f_ps, f_theta_rhodz, f_ue, f_q) CASE DEFAULT PRINT*, 'Bad selector for variable physics <',TRIM(physics_type), & '> options are , , ' STOP END SELECT END SUBROUTINE physics END MODULE physics_mod