Changeset 848


Ignore:
Timestamp:
05/05/19 00:39:29 (5 years ago)
Author:
dubos
Message:

devel : reorganized etat0_collocated.f90

File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/devel/src/initial/etat0_collocated.f90

    r847 r848  
    66  PRIVATE 
    77 
    8     CHARACTER(len=255),SAVE :: etat0_type 
    9 !$OMP THREADPRIVATE(etat0_type) 
     8  LOGICAL :: autoinit_mass, autoinit_NH 
     9  CHARACTER(len=255),SAVE :: etat0_type 
     10!$OMP THREADPRIVATE(autoinit_mass, autoinit_NH, etat0_type) 
    1011 
    1112    PUBLIC :: etat0_type, etat0_collocated 
     
    6465 
    6566      IF( TRIM(etat0_type)=='williamson91.6' ) THEN 
    66          CALL compute_etat0_collocated(ps,mass, phis, theta_rhodz(:,:,1), u, geopot, W, q) 
     67         CALL compute_etat0_collocated_hex(ps,mass, phis, theta_rhodz(:,:,1), u, geopot, W, q) 
    6768      ELSE 
    68          CALL compute_etat0_collocated(ps,mass, phis, temp, u, geopot, W, q) 
     69         CALL compute_etat0_collocated_hex(ps,mass, phis, temp, u, geopot, W, q) 
    6970      ENDIF 
    7071 
     
    128129  END SUBROUTINE compute_temperature2entropy 
    129130 
    130   SUBROUTINE compute_etat0_collocated(ps,mass,phis,temp_i,u, geopot,W, q) 
     131  SUBROUTINE compute_etat0_collocated_hex(ps,mass,phis,temp_i,u, geopot,W, q) 
    131132    USE wind_mod 
    132133    USE disvert_mod 
    133     USE etat0_isothermal_mod, ONLY : compute_isothermal => compute_etat0 
    134     USE etat0_jablonowsky06_mod, ONLY : compute_jablonowsky06 => compute_etat0 
    135     USE etat0_dcmip1_mod, ONLY : compute_dcmip1 => compute_etat0 
    136     USE etat0_dcmip2_mod, ONLY : compute_dcmip2 => compute_etat0 
    137     USE etat0_dcmip3_mod, ONLY : compute_dcmip3 => compute_etat0 
    138     USE etat0_dcmip4_mod, ONLY : compute_dcmip4 => compute_etat0 
    139     USE etat0_dcmip5_mod, ONLY : compute_dcmip5 => compute_etat0 
    140     USE etat0_bubble_mod, ONLY : compute_bubble => compute_etat0   
    141     USE etat0_williamson_mod, ONLY : compute_w91_6 => compute_etat0 
    142     USE etat0_temperature_mod, ONLY: compute_temperature => compute_etat0 
    143     USE etat0_dcmip2016_baroclinic_wave_mod, ONLY : compute_dcmip2016_baroclinic_wave => compute_etat0 
    144     USE etat0_dcmip2016_cyclone_mod, ONLY : compute_dcmip2016_cyclone => compute_etat0 
    145     USE etat0_dcmip2016_supercell_mod, ONLY : compute_dcmip2016_supercell => compute_etat0 
    146134    REAL(rstd),INTENT(INOUT) :: ps(iim*jjm) 
    147135    REAL(rstd),INTENT(INOUT) :: mass(iim*jjm,llm) 
     
    167155    INTEGER :: l,i,j,ij 
    168156    REAL :: p_ik, v_ik, mass_ik 
    169     LOGICAL :: autoinit_mass, autoinit_NH 
    170157 
    171158    ! For NH geopotential and vertical momentum must be initialized. 
     
    176163    w(:,:) = 0 
    177164 
    178     SELECT CASE (TRIM(etat0_type)) 
    179     CASE ('isothermal') 
    180        CALL compute_isothermal(iim*jjm, phis, ps, temp_i, ulon_i, ulat_i, q) 
    181        CALL compute_isothermal(3*iim*jjm, phis_e, ps_e, temp_e, ulon_e, ulat_e, q_e) 
    182     CASE ('temperature_profile') 
    183        CALL compute_temperature(iim*jjm, phis, ps, temp_i, ulon_i, ulat_i, q) 
    184        CALL compute_temperature(3*iim*jjm, phis_e, ps_e, temp_e, ulon_e, ulat_e, q_e) 
    185     CASE('jablonowsky06') 
    186        CALL compute_jablonowsky06(iim*jjm,lon_i,lat_i, phis, ps, temp_i, ulon_i, ulat_i) 
    187        CALL compute_jablonowsky06(3*iim*jjm,lon_e,lat_e, phis_e, ps_e, temp_e, ulon_e, ulat_e) 
    188     CASE('dcmip1') 
    189        CALL compute_dcmip1(iim*jjm,lon_i,lat_i, phis, ps, temp_i, ulon_i, ulat_i, q) 
    190        CALL compute_dcmip1(3*iim*jjm,lon_e,lat_e, phis_e, ps_e, temp_e, ulon_e, ulat_e, q_e) 
    191     CASE ('dcmip2_mountain','dcmip2_schaer_noshear','dcmip2_schaer_shear') 
    192        CALL compute_dcmip2(iim*jjm,lon_i,lat_i, phis, ps, temp_i, ulon_i, ulat_i) 
    193        CALL compute_dcmip2(3*iim*jjm,lon_e,lat_e, phis_e, ps_e, temp_e, ulon_e, ulat_e)       
    194     CASE('dcmip3') 
    195        CALL compute_dcmip3(iim*jjm,lon_i,lat_i, phis, ps, temp_i, ulon_i, ulat_i, geopot, q) 
    196        CALL compute_dcmip3(3*iim*jjm,lon_e,lat_e, phis_e, ps_e, temp_e, ulon_e, ulat_e, geopot_e, q_e) 
    197        autoinit_NH = .FALSE. ! compute_dcmip3 initializes geopot 
    198     CASE('dcmip4') 
    199        CALL compute_dcmip4(iim*jjm,lon_i,lat_i, phis, ps, temp_i, ulon_i, ulat_i, q) 
    200        CALL compute_dcmip4(3*iim*jjm,lon_e,lat_e, phis_e, ps_e, temp_e, ulon_e, ulat_e, q_e) 
    201     CASE('dcmip5') 
    202        CALL compute_dcmip5(iim*jjm,lon_i,lat_i, phis, ps, temp_i, ulon_i, ulat_i, q) 
    203        CALL compute_dcmip5(3*iim*jjm,lon_e,lat_e, phis_e, ps_e, temp_e, ulon_e, ulat_e, q_e) 
    204     CASE('bubble') 
    205        CALL compute_bubble(iim*jjm,lon_i,lat_i, phis, ps, temp_i, ulon_i, ulat_i, geopot, q) 
    206        CALL compute_bubble(3*iim*jjm,lon_e,lat_e, phis_e, ps_e, temp_e, ulon_e, ulat_e, geopot_e, q_e) 
    207 !       autoinit_NH = .FALSE. ! compute_bubble initializes geopot 
    208     CASE('williamson91.6') 
    209        CALL compute_w91_6(iim*jjm,lon_i,lat_i, phis, mass(:,1), temp_i(:,1), ulon_i(:,1), ulat_i(:,1)) 
    210        CALL compute_w91_6(3*iim*jjm,lon_e,lat_e, phis_e, mass_e(:,1), temp_e(:,1), ulon_e(:,1), ulat_e(:,1)) 
    211        autoinit_mass = .FALSE. ! do not overwrite mass 
    212     CASE('dcmip2016_baroclinic_wave') 
    213        CALL compute_dcmip2016_baroclinic_wave(iim*jjm,lon_i,lat_i, phis, ps, temp_i, ulon_i, ulat_i, q) 
    214        CALL compute_dcmip2016_baroclinic_wave(3*iim*jjm,lon_e,lat_e, phis_e, ps_e, temp_e, ulon_e, ulat_e, q_e) 
    215     CASE('dcmip2016_cyclone') 
    216        CALL compute_dcmip2016_cyclone(iim*jjm,lon_i,lat_i, phis, ps, temp_i, ulon_i, ulat_i, q) 
    217        CALL compute_dcmip2016_cyclone(3*iim*jjm,lon_e,lat_e, phis_e, ps_e, temp_e, ulon_e, ulat_e, q_e) 
    218     CASE('dcmip2016_supercell') 
    219        CALL compute_dcmip2016_supercell(iim*jjm,lon_i,lat_i, phis, ps, temp_i, ulon_i, ulat_i, q) 
    220        CALL compute_dcmip2016_supercell(3*iim*jjm,lon_e,lat_e, phis_e, ps_e, temp_e, ulon_e, ulat_e, q_e) 
    221     END SELECT 
     165    CALL compute_etat0_collocated(iim*jjm  , lon_i, lat_i, phis,   ps,   mass,   temp_i, ulon_i, ulat_i, geopot,   q) 
     166    CALL compute_etat0_collocated(3*iim*jjm, lon_e, lat_e, phis_e, ps_e, mass_e, temp_e, ulon_e, ulat_e, geopot_e, q_e) 
    222167 
    223168    IF(autoinit_mass) CALL compute_rhodz(.TRUE., ps, mass) ! initialize mass distribution using ps 
     
    238183    CALL compute_wind_perp_from_lonlat_compound(ulon_e, ulat_e, u) 
    239184 
     185  END SUBROUTINE compute_etat0_collocated_hex 
     186 
     187  SUBROUTINE compute_etat0_collocated(ngrid, lon, lat, phis, ps, mass, temp, ulon, ulat, geopot, q) 
     188    USE etat0_isothermal_mod, ONLY : compute_isothermal => compute_etat0 
     189    USE etat0_jablonowsky06_mod, ONLY : compute_jablonowsky06 => compute_etat0 
     190    USE etat0_dcmip1_mod, ONLY : compute_dcmip1 => compute_etat0 
     191    USE etat0_dcmip2_mod, ONLY : compute_dcmip2 => compute_etat0 
     192    USE etat0_dcmip3_mod, ONLY : compute_dcmip3 => compute_etat0 
     193    USE etat0_dcmip4_mod, ONLY : compute_dcmip4 => compute_etat0 
     194    USE etat0_dcmip5_mod, ONLY : compute_dcmip5 => compute_etat0 
     195    USE etat0_bubble_mod, ONLY : compute_bubble => compute_etat0   
     196    USE etat0_williamson_mod, ONLY : compute_w91_6 => compute_etat0 
     197    USE etat0_temperature_mod, ONLY: compute_temperature => compute_etat0 
     198    USE etat0_dcmip2016_baroclinic_wave_mod, ONLY : compute_dcmip2016_baroclinic_wave => compute_etat0 
     199    USE etat0_dcmip2016_cyclone_mod, ONLY : compute_dcmip2016_cyclone => compute_etat0 
     200    USE etat0_dcmip2016_supercell_mod, ONLY : compute_dcmip2016_supercell => compute_etat0 
     201    INTEGER :: ngrid 
     202    REAL(rstd),INTENT(IN)    :: lon(ngrid), lat(ngrid) 
     203    REAL(rstd),INTENT(INOUT) :: ps(ngrid) 
     204    REAL(rstd),INTENT(INOUT) :: mass(ngrid,llm) 
     205    REAL(rstd),INTENT(OUT)   :: phis(ngrid) 
     206    REAL(rstd),INTENT(OUT)   :: temp(ngrid,llm) 
     207    REAL(rstd),INTENT(OUT)   :: ulon(ngrid,llm) 
     208    REAL(rstd),INTENT(OUT)   :: ulat(ngrid,llm) 
     209    REAL(rstd),INTENT(OUT)   :: geopot(ngrid,llm+1) 
     210    REAL(rstd),INTENT(OUT)   :: q(ngrid,llm,nqtot) 
     211 
     212    SELECT CASE (TRIM(etat0_type)) 
     213    CASE ('isothermal') 
     214       CALL compute_isothermal(ngrid, phis, ps, temp, ulon, ulat, q) 
     215    CASE ('temperature_profile') 
     216       CALL compute_temperature(ngrid, phis, ps, temp, ulon, ulat, q) 
     217    CASE('jablonowsky06') 
     218       CALL compute_jablonowsky06(ngrid, lon, lat, phis, ps, temp, ulon, ulat) 
     219    CASE('dcmip1') 
     220       CALL compute_dcmip1(ngrid, lon, lat, phis, ps, temp, ulon, ulat, q) 
     221    CASE ('dcmip2_mountain','dcmip2_schaer_noshear','dcmip2_schaer_shear') 
     222       CALL compute_dcmip2(ngrid, lon, lat, phis, ps, temp, ulon, ulat) 
     223    CASE('dcmip3') 
     224       CALL compute_dcmip3(ngrid, lon, lat, phis, ps, temp, ulon, ulat, geopot, q) 
     225       autoinit_NH = .FALSE. ! compute_dcmip3 initializes geopot 
     226    CASE('dcmip4') 
     227       CALL compute_dcmip4(ngrid, lon, lat, phis, ps, temp, ulon, ulat, q) 
     228    CASE('dcmip5') 
     229       CALL compute_dcmip5(ngrid, lon, lat, phis, ps, temp, ulon, ulat, q) 
     230    CASE('bubble') 
     231       CALL compute_bubble(ngrid, lon, lat, phis, ps, temp, ulon, ulat, geopot, q) 
     232!       autoinit_NH = .FALSE. ! compute_bubble initializes geopot 
     233    CASE('williamson91.6') 
     234       CALL compute_w91_6(ngrid, lon, lat, phis, mass(:,1), temp(:,1), ulon(:,1), ulat(:,1)) 
     235       autoinit_mass = .FALSE. ! do not overwrite mass 
     236    CASE('dcmip2016_baroclinic_wave') 
     237       CALL compute_dcmip2016_baroclinic_wave(ngrid, lon, lat, phis, ps, temp, ulon, ulat, q) 
     238    CASE('dcmip2016_cyclone') 
     239       CALL compute_dcmip2016_cyclone(ngrid, lon, lat, phis, ps, temp, ulon, ulat, q) 
     240    CASE('dcmip2016_supercell') 
     241       CALL compute_dcmip2016_supercell(ngrid, lon, lat, phis, ps, temp, ulon, ulat, q) 
     242    END SELECT 
     243 
    240244  END SUBROUTINE compute_etat0_collocated 
    241245 
Note: See TracChangeset for help on using the changeset viewer.