Changeset 884


Ignore:
Timestamp:
06/12/19 00:27:36 (5 years ago)
Author:
dubos
Message:

devel/unstructured : fixed etat0 + renamed compute => compute_caldyn

Location:
codes/icosagcm/devel/src
Files:
4 edited
1 moved

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/devel/src/dynamics/caldyn_gcm.F90

    r861 r884  
    1616   
    1717  SUBROUTINE init_caldyn 
    18     USE compute_mod, ONLY : compute_pvort_only 
     18    USE compute_caldyn_mod, ONLY : compute_pvort_only 
    1919    USE compute_pvort_only_mod, ONLY : compute_pvort_only_hex, compute_pvort_only_unst 
    2020 
  • codes/icosagcm/devel/src/dynamics/caldyn_hevi.f90

    r861 r884  
    3434    USE output_field_mod 
    3535    USE checksum_mod 
    36     USE compute_mod, ONLY : compute_pvort_only 
     36    USE compute_caldyn_mod, ONLY : compute_pvort_only 
    3737    IMPLICIT NONE 
    3838    LOGICAL,INTENT(IN)    :: write_out 
  • codes/icosagcm/devel/src/dynamics/compute_caldyn.f90

    r882 r884  
    1 MODULE compute_mod 
     1MODULE compute_caldyn_mod 
    22  IMPLICIT NONE 
    33  SAVE 
     
    1818  PROCEDURE(comp_pvort_only), POINTER :: compute_pvort_only => NULL() 
    1919 
    20 END MODULE compute_mod 
     20END MODULE compute_caldyn_mod 
  • codes/icosagcm/devel/src/dynamics/compute_pvort_only.F90

    r852 r884  
    11MODULE compute_pvort_only_mod 
    2   USE compute_mod, ONLY : comp_pvort_only 
    32  USE grid_param, ONLY : llm 
    43  IMPLICIT NONE 
     
    1211 
    1312  SUBROUTINE check_interface 
    14     PROCEDURE(comp_pvort_only), POINTER :: ptr 
    15     ptr => compute_pvort_only_unst 
    16     ptr => compute_pvort_only_hex 
     13    USE compute_caldyn_mod 
     14    compute_pvort_only => compute_pvort_only_unst 
     15    compute_pvort_only => compute_pvort_only_hex 
    1716  END SUBROUTINE check_interface 
    1817   
  • codes/icosagcm/devel/src/initial/etat0_collocated.f90

    r856 r884  
    114114    REAL(rstd) :: phis_e(edge_num) 
    115115    REAL(rstd) :: u_e(edge_num, llm) 
     116    REAL(rstd) :: ep(edge_num,3) 
    116117    REAL(rstd) :: mass_i(primal_num, llm), theta_rhodz_i(primal_num, llm), mass_e(edge_num, llm) 
    117118    REAL(rstd) :: geopot_i(edge_num, llm+1), geopot_e(edge_num, llm+1) 
     
    120121 
    121122    w(:,:) = 0 
     123    ep = TRANSPOSE(ep_e) 
    122124    CALL compute_etat0_collocated(primal_num  , lon_i, lat_i, phis,   ps,   mass_i,   theta_rhodz_i, geopot_i,   q_i) 
    123     CALL compute_etat0_collocated(edge_num, lon_e, lat_e, phis_e, ps_e, mass_e, mass_e, geopot_e, q_e, ep_e, u_e) 
     125    CALL compute_etat0_collocated(edge_num, lon_e, lat_e, phis_e, ps_e, mass_e, mass_e, geopot_e, q_e, ep, u_e) 
    124126    mass = TRANSPOSE(mass_i) 
    125127    theta_rhodz = TRANSPOSE(theta_rhodz_i) 
Note: See TracChangeset for help on using the changeset viewer.