Changeset 581


Ignore:
Timestamp:
10/13/17 16:00:58 (7 years ago)
Author:
dubos
Message:

trunk : upgrading to devel

Location:
codes/icosagcm/trunk/src
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/trunk/src/diagnostics/observable.f90

    r548 r581  
    55 
    66  TYPE(t_field),POINTER, SAVE :: f_buf_i(:), & 
    7        f_buf_uh(:), & ! horizontal velocity, different from prognostic velocity if NH 
     7       f_buf_Fel(:), f_buf_uh(:), & ! horizontal velocity, different from prognostic velocity if NH 
    88       f_buf_ulon(:), f_buf_ulat(:), & 
    99       f_buf_u3d(:) ! unused, remove ? 
     
    2828    CALL allocate_field(f_buf_ulat,field_t,type_real,llm, name="buf_ulat") 
    2929    CALL allocate_field(f_buf_uh,  field_u,type_real,llm, name="buf_uh") 
     30    CALL allocate_field(f_buf_Fel, field_u,type_real,llm+1, name="buf_F_el") 
    3031    CALL allocate_field(f_buf_v,   field_z,type_real,llm, name="buf_v") 
    3132    CALL allocate_field(f_buf_s,   field_t,type_real, name="buf_s") 
     
    6061     
    6162    IF(init) THEN 
     63       IF(is_master) PRINT *, 'Creating output files ...' 
    6264       scalar(1)=dt 
    6365       IF (is_omp_master) CALL xios_send_field("timestep", scalar) 
     
    7476 
    7577       CALL output_field("phis",f_phis) 
    76        CALL output_field("Ai",geom%Ai)        
     78       CALL output_field("Ai",geom%Ai)  
     79       IF(is_master) PRINT *, '... done creating output files. Writing initial condition ...' 
    7780    END IF 
    7881 
     
    120123       CALL output_field("geopot_init",f_geopot) 
    121124       CALL output_field("q_init",f_q) 
     125       IF(is_master) PRINT *, 'Done writing initial condition ...' 
    122126    ELSE 
    123127       CALL output_field("uz",f_buf_i) 
     
    165169         f_u(:), f_W(:), f_uz(:), &  ! IN 
    166170         f_uh(:)                         ! OUT 
    167     REAL(rstd),POINTER :: geopot(:,:), ps(:), rhodz(:,:), u(:,:), W(:,:), uh(:,:), uz(:,:) 
     171    REAL(rstd),POINTER :: geopot(:,:), ps(:), rhodz(:,:), u(:,:), W(:,:), uh(:,:), uz(:,:), F_el(:,:) 
    168172    INTEGER :: ind 
    169173     
     
    177181       W = f_W(ind) 
    178182       uh  = f_uh(ind) 
     183       F_el  = f_buf_Fel(ind) 
    179184       IF(caldyn_eta==eta_mass) THEN 
    180185          ps=f_ps(ind) 
     
    182187       END IF 
    183188       uz = f_uz(ind) 
    184        CALL compute_prognostic_vel_to_horiz(geopot,rhodz,u,W,uh,uz) 
     189       !$OMP BARRIER 
     190       CALL compute_prognostic_vel_to_horiz(geopot,rhodz,u,W, F_el, uh,uz) 
     191       !$OMP BARRIER 
    185192    END DO 
    186193  END SUBROUTINE progonostic_vel_to_horiz 
    187194   
    188   SUBROUTINE compute_prognostic_vel_to_horiz(Phi, rhodz, u, W, uh, uz) 
     195  SUBROUTINE compute_prognostic_vel_to_horiz(Phi, rhodz, u, W, F_el, uh, uz) 
    189196    USE omp_para 
    190197    REAL(rstd), INTENT(IN) :: Phi(iim*jjm,llm+1) 
     
    220227       END DO 
    221228 
     229       ! We need a barrier here because we compute F_el above and do a vertical average below 
     230       !$OMP BARRIER 
     231 
    222232       DO l=ll_begin, ll_end ! compute on k levels (full levels) 
    223233          DO ij=ij_begin_ext, ij_end_ext 
  • codes/icosagcm/trunk/src/initial/etat0.f90

    r548 r581  
    11MODULE etat0_mod 
    22  USE icosa 
     3  USE omp_para 
    34  IMPLICIT NONE          
    45  PRIVATE 
     
    1011 
    1112    PUBLIC :: etat0, init_etat0, etat0_type 
     13 
     14! Important notes for OpenMP 
     15! When etat0 is called, vertical OpenMP parallelism is deactivated.  
     16! Therefore only the omp_level_master thread must work, i.e. : 
     17!   !$OMP BARRIER 
     18!    DO ind=1,ndomain 
     19!      IF (.NOT. assigned_domain(ind) .OR. .NOT. is_omp_level_master) CYCLE 
     20!      ... 
     21!    END DO 
     22!   !$OMP BARRIER 
     23! There MUST be NO OMP BARRIER inside the DO-LOOP or any routine it calls. 
    1224 
    1325CONTAINS 
    1426   
    1527  SUBROUTINE init_etat0 
    16   USE etat0_database_mod, ONLY: init_etat0_database => init_etat0  
    17   USE etat0_start_file_mod, ONLY: init_etat0_start_file => init_etat0  
    18   USE etat0_heldsz_mod, ONLY: init_etat0_held_suarez => init_etat0  
    19   IMPLICIT NONE 
    20  
     28    USE etat0_database_mod, ONLY: init_etat0_database => init_etat0  
     29    USE etat0_start_file_mod, ONLY: init_etat0_start_file => init_etat0  
     30    USE etat0_heldsz_mod, ONLY: init_etat0_held_suarez => init_etat0  
     31     
    2132    CALL getin("etat0",etat0_type) 
    2233 
     
    7586    USE etat0_start_file_mod, ONLY : etat0_start_file=>etat0   
    7687 
    77     IMPLICIT NONE 
    7888    TYPE(t_field),POINTER :: f_ps(:) 
    7989    TYPE(t_field),POINTER :: f_mass(:) 
     
    160170    END SELECT 
    161171 
    162 !       !$OMP BARRIER 
    163172    IF(autoinit_mass) THEN 
    164173       DO ind=1,ndomain 
    165           IF (.NOT. assigned_domain(ind)) CYCLE 
     174          IF (.NOT. assigned_domain(ind) .OR. .NOT. is_omp_level_master) CYCLE 
    166175          CALL swap_dimensions(ind) 
    167176          CALL swap_geometry(ind) 
     
    175184  SUBROUTINE etat0_collocated(f_phis,f_ps,f_mass,f_theta_rhodz,f_u, f_geopot,f_W, f_q) 
    176185    USE theta2theta_rhodz_mod 
    177     IMPLICIT NONE 
    178186    TYPE(t_field),POINTER :: f_ps(:) 
    179187    TYPE(t_field),POINTER :: f_mass(:) 
     
    200208 
    201209    DO ind=1,ndomain 
    202       IF (.NOT. assigned_domain(ind)) CYCLE 
     210      IF (.NOT. assigned_domain(ind) .OR. .NOT. is_omp_level_master) CYCLE 
     211!      IF (.NOT. assigned_domain(ind)) CYCLE 
    203212      CALL swap_dimensions(ind) 
    204213      CALL swap_geometry(ind) 
     
    232241    USE exner_mod 
    233242    USE omp_para 
    234     IMPLICIT NONE 
    235243    REAL(rstd),INTENT(IN)  :: ps(iim*jjm) 
    236244    REAL(rstd),INTENT(IN)  :: temp(iim*jjm,llm) 
     
    248256    CALL compute_pression(ps,p,offset) 
    249257    ! flush p 
    250     !$OMP BARRIER 
    251258    DO    l    = ll_begin, ll_end 
    252259       DO j=jj_begin-offset,jj_end+offset 
     
    278285       ENDDO 
    279286    ENDDO 
    280     !$OMP BARRIER   
    281287  END SUBROUTINE compute_temperature2entropy 
    282288 
     
    296302    USE etat0_dcmip2016_cyclone_mod, ONLY : compute_dcmip2016_cyclone => compute_etat0 
    297303    USE etat0_dcmip2016_supercell_mod, ONLY : compute_dcmip2016_supercell => compute_etat0 
    298     IMPLICIT NONE 
    299304    REAL(rstd),INTENT(INOUT) :: ps(iim*jjm) 
    300305    REAL(rstd),INTENT(INOUT) :: mass(iim*jjm,llm) 
     
    328333    autoinit_NH = .NOT. hydrostatic 
    329334    w(:,:) = 0 
    330  
    331     !$OMP BARRIER 
    332335 
    333336    SELECT CASE (TRIM(etat0_type)) 
     
    391394    END IF 
    392395 
    393     !$OMP BARRIER 
    394  
    395396    CALL compute_wind_perp_from_lonlat_compound(ulon_e, ulat_e, u) 
    396397 
     
    405406 
    406407  SUBROUTINE compute_etat0_isothermal(ngrid, phis, ps, temp, ulon, ulat, q) 
    407     IMPLICIT NONE   
    408408    INTEGER, INTENT(IN)    :: ngrid 
    409409    REAL(rstd),INTENT(OUT) :: phis(ngrid) 
  • codes/icosagcm/trunk/src/output/write_etat0.f90

    r548 r581  
    55CONTAINS 
    66 
    7   SUBROUTINE write_etat0(it,f_ps,f_phis,f_theta_rhodz,f_u, f_q) 
     7  SUBROUTINE write_etat0(it,f_ps,f_phis,f_theta_rhodz,f_u, f_q, f_geopot, f_W) 
    88  USE icosa 
    99  USE restart_mod 
     
    2020    TYPE(t_field),POINTER :: f_u(:) 
    2121    TYPE(t_field),POINTER :: f_q(:) 
     22    TYPE(t_field),POINTER, OPTIONAL :: f_geopot(:) 
     23    TYPE(t_field),POINTER, OPTIONAL :: f_W(:) 
    2224   
    2325    TYPE(t_field),POINTER,SAVE :: f_ulon(:) 
     
    4143    CALL transfert_request(f_u,req_e1_vect) 
    4244    CALL un2ulonlat(f_u, f_ulon, f_ulat) 
    43      
    44     CALL write_restart(it,f_ps,f_phis,f_theta_rhodz_1d,f_u, f_ulon, f_ulat, f_q) 
    4545 
     46    IF(hydrostatic) THEN 
     47       CALL write_restart(it,f_ps,f_phis,f_theta_rhodz_1d,f_u, f_ulon, f_ulat, f_q) 
     48    ELSE 
     49       CALL write_restart(it,f_ps,f_phis,f_theta_rhodz_1d,f_u, f_ulon, f_ulat, f_q, f_geopot, f_W) 
     50    END IF 
    4651    CALL deallocate_field(f_ulon) 
    4752    CALL deallocate_field(f_ulat) 
  • codes/icosagcm/trunk/src/time/timeloop_gcm.f90

    r548 r581  
    219219    END IF 
    220220     
    221     IF (write_start) CALL write_etat0(itau0,f_ps, f_phis,f_theta_rhodz,f_u,f_q)  ! FIXME : write_start undefined 
     221!    IF (write_start) CALL write_etat0(itau0,f_ps, f_phis,f_theta_rhodz,f_u,f_q) 
     222    IF (write_start) CALL write_etat0(itau0,f_ps, f_phis,f_theta_rhodz,f_u,f_q, f_geopot, f_W) 
    222223    
    223224    CALL write_output_fields_basic(.TRUE., f_phis, f_ps, f_mass, f_geopot, f_theta_rhodz, f_u, f_W, f_q) 
     
    337338    END DO 
    338339     
    339     CALL write_etat0(itau0+itaumax,f_ps, f_phis,f_theta_rhodz,f_u,f_q)  
     340!    CALL write_etat0(itau0+itaumax,f_ps, f_phis,f_theta_rhodz,f_u,f_q)  
     341    CALL write_etat0(itau0+itaumax,f_ps, f_phis,f_theta_rhodz,f_u,f_q, f_geopot, f_W)  
    340342     
    341343    CALL check_conserve_detailed(it, AAM_dyn, & 
Note: See TracChangeset for help on using the changeset viewer.