Changeset 949


Ignore:
Timestamp:
07/13/19 17:01:16 (5 years ago)
Author:
dubos
Message:

devel : generic compute_caldyn_slow_hydro + fixes

Location:
codes/icosagcm/devel/src
Files:
5 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/devel/src/base/init_grid_param.f90

    r938 r949  
    8585    compute_pvort_only         => compute_pvort_only_unst 
    8686    compute_theta              => compute_theta_unst 
    87 !    compute_geopot           => compute_geopot_unst 
     87    compute_geopot             => compute_geopot_unst 
    8888    compute_caldyn_fast        => compute_caldyn_fast_unst 
    8989    compute_caldyn_slow_hydro  => compute_caldyn_slow_hydro_unst 
    90     compute_caldyn_coriolis   => compute_caldyn_coriolis_unst 
     90    compute_caldyn_coriolis    => compute_caldyn_coriolis_unst 
    9191  END SUBROUTINE select_compute_unst 
    9292   
  • codes/icosagcm/devel/src/dynamics/caldyn_hevi.f90

    r938 r949  
    66  USE compute_caldyn_vert_NH_mod, ONLY : compute_caldyn_vert_NH => compute_caldyn_vert_NH_manual 
    77  USE compute_caldyn_kv_mod, ONLY : compute_caldyn_kv 
    8   USE compute_caldyn_slow_hydro_mod, ONLY : compute_caldyn_slow_hydro => compute_caldyn_slow_hydro_manual 
    98  USE compute_caldyn_slow_NH_mod, ONLY : compute_caldyn_slow_NH 
    109  USE compute_caldyn_solver_mod, ONLY : compute_caldyn_solver 
     
    3231    USE checksum_mod 
    3332    USE compute_caldyn_mod, ONLY : compute_pvort_only, compute_theta, & 
    34          compute_geopot, compute_caldyn_fast, compute_caldyn_coriolis 
     33         compute_geopot, compute_caldyn_fast, compute_caldyn_coriolis, compute_caldyn_slow_hydro 
    3534    IMPLICIT NONE 
    3635    LOGICAL,INTENT(IN)    :: write_out 
  • codes/icosagcm/devel/src/time/timeloop_gcm.f90

    r909 r949  
    252252    !$OMP END MASTER    
    253253 
    254     IF(grid_type == grid_unst) RETURN 
    255  
    256254    DO it=itau0+1,itau0+itaumax 
    257255       IF (is_master) CALL print_iteration(it, itau0, itaumax, start_clock, rate_clock) 
  • codes/icosagcm/devel/src/unstructured/data_unstructured.F90

    r940 r949  
    55  USE grid_param, ONLY : llm, nqdyn, primal_num, edge_num, dual_num, & 
    66       max_primal_deg, max_dual_deg, max_trisk_deg 
    7   USE geometry, ONLY : le, le_de, fv, Av, Ai 
     7  USE geometry, ONLY : le, le_de, fv, Av, Ai, wee, Riv2 
    88#ifdef CPP_USING_OMP 
    99  USE OMP_LIB 
     
    4343  NUM1(max_nb_stage), BIND(C)              :: tauj       ! diagonal of fast Butcher tableau 
    4444  NUM2(max_nb_stage,max_nb_stage), BIND(C) :: cslj, cflj ! slow and fast modified Butcher tableaus 
    45   NUM2(:,:), POINTER          :: centroid, xyz_v, Riv2, ap,bp, mass_bl, mass_dak, mass_dbk 
    46   NUM3(:,:,:), POINTER        :: wee 
     45  NUM2(:,:), POINTER          :: centroid, xyz_v, ap,bp, mass_bl, mass_dak, mass_dbk 
    4746  INTEGER(C_INT), BIND(C) :: comm_icosa 
    4847 
  • codes/icosagcm/devel/src/unstructured/init_unstructured.f90

    r940 r949  
    219219    USE field_mod 
    220220    USE domain_mod, ONLY : swap_needed, domain, domain_glo 
    221     USE geometry, ONLY : geom, lon_i, lat_i, lon_e, lat_e, ep_e 
     221    USE geometry, ONLY : geom, lon_i, lat_i, lon_e, lat_e, ep_e, Riv2, wee 
    222222    USE netcdf_mod, ONLY : nf90_close 
    223223    IMPLICIT NONE 
     
    242242    swap_needed = .TRUE. 
    243243    CALL swap_geometry(1) 
     244    swap_needed = .FALSE. 
    244245     
    245246    PRINT *, 'read_local_mesh : primal_num =', primal_num, domain_glo(1)%primal_own%ncell 
     
    311312    DEALLOCATE(angle_e) 
    312313 
    313     CALL swap_geometry(1) 
    314     swap_needed = .FALSE. 
    315  
    316314  END SUBROUTINE read_local_mesh 
    317315 
Note: See TracChangeset for help on using the changeset viewer.