Changeset db712a8 in flexpart.git for src/mpi_mod.f90


Ignore:
Timestamp:
Mar 3, 2016, 12:34:56 PM (8 years ago)
Author:
Espen Sollum ATMOS <eso@…>
Branches:
master, 10.4.1_pesei, GFS_025, bugfixes+enhancements, dev, release-10, release-10.4.1, scaling-bug, univie
Children:
38b7917
Parents:
b0434e1
Message:

Completed handling of nested wind fields with cloud water (for wet deposition).

File:
1 edited

Legend:

Unmodified
Added
Removed
  • src/mpi_mod.f90

    r6a678e3 rdb712a8  
    860860!   step
    861861!
    862 ! TODO
    863 !   GFS version
    864862!
    865863!*******************************************************************************
     
    922920
    923921! The non-reader processes need to know if cloud water were read.
    924 ! TODO: only at first step or always?
    925922    call MPI_Bcast(readclouds,1,MPI_LOGICAL,id_read,MPI_COMM_WORLD,mp_ierr)
    926923    if (mp_ierr /= 0) goto 600
     
    10171014    if (mp_ierr /= 0) goto 600
    10181015
    1019     call MPI_Bcast(z0,numclass,mp_sp,id_read,MPI_COMM_WORLD,mp_ierr)
    1020     if (mp_ierr /= 0) goto 600
    1021 
    10221016    if (mp_measure_time) call mpif_mtime('commtime',1)
    10231017
     
    10451039!   step
    10461040!
    1047 ! TODO
    1048 !   Transfer cloud water/ice if and when available for nested
    10491041!
    10501042!***********************************************************************
     
    10601052
    10611053! Common array sizes used for communications
    1062     integer :: d3_size1 = nxmaxn*nymaxn*nzmax*maxnests
    1063     integer :: d3_size2 = nxmaxn*nymaxn*nuvzmax*maxnests
    1064     integer :: d2_size1 = nxmaxn*nymaxn*maxnests
    1065     integer :: d2_size2 = nxmaxn*nymaxn*maxspec*maxnests
    1066     integer :: d2_size3 = nxmaxn*nymaxn*maxnests
     1054    integer :: d3_size1 = nxmaxn*nymaxn*nzmax
     1055    integer :: d3_size2 = nxmaxn*nymaxn*nuvzmax
     1056    integer :: d2_size1 = nxmaxn*nymaxn
     1057    integer :: d2_size2 = nxmaxn*nymaxn*maxspec
     1058    integer :: d2_size3 = nxmaxn*nymaxn
    10671059
    10681060    integer :: d3s1,d3s2,d2s1,d2s2
     
    11061098!**********************************************************************
    11071099
     1100! The non-reader processes need to know if cloud water were read.
     1101    call MPI_Bcast(readclouds_nest,maxnests,MPI_LOGICAL,id_read,MPI_COMM_WORLD,mp_ierr)
     1102    if (mp_ierr /= 0) goto 600
     1103
    11081104! Static fields/variables sent only at startup
    11091105    if (first_call) then
     
    11201116
    11211117! MPI prefers contiguous arrays for sending (else a buffer is created),
    1122 ! hence the loop
    1123 
     1118! hence the loop over nests
     1119!**********************************************************************
    11241120    do i=1, numbnests
    11251121! 3D fields
     
    11451141      if (mp_ierr /= 0) goto 600
    11461142      call MPI_Bcast(cloudsn(:,:,:,li:ui,i),d3s1,MPI_INTEGER1,id_read,MPI_COMM_WORLD,mp_ierr)
    1147       if (mp_ierr /= 0) goto 600
     1143      if (mp_ierr /= 0) goto 600
     1144
     1145! cloud water/ice:
     1146    if (readclouds_nest(i)) then
     1147      ! call MPI_Bcast(icloud_stats(:,:,:,li:ui),d2s1*5,mp_sp,id_read,MPI_COMM_WORLD,mp_ierr)
     1148      ! if (mp_ierr /= 0) goto 600
     1149      call MPI_Bcast(clw4n(:,:,li:ui,i),d2s1,mp_sp,id_read,MPI_COMM_WORLD,mp_ierr)
     1150      if (mp_ierr /= 0) goto 600
     1151    end if
    11481152
    11491153! 2D fields
    1150       call MPI_Bcast(cloudsnh(:,:,li:ui,i),d2s1,mp_sp,id_read,MPI_COMM_WORLD,mp_ierr)
     1154      call MPI_Bcast(cloudshn(:,:,li:ui,i),d2s1,mp_sp,id_read,MPI_COMM_WORLD,mp_ierr)
    11511155      if (mp_ierr /= 0) goto 600
    11521156      call MPI_Bcast(vdepn(:,:,:,li:ui,i),d2s2,mp_sp,id_read,MPI_COMM_WORLD,mp_ierr)
     
    12061210!   mind    -- index where to place new fields
    12071211!
    1208 ! TODO
    12091212!
    12101213!*******************************************************************************
     
    13921395!   memstat -- input, used to resolve windfield index being received
    13931396!
    1394 ! TODO
    13951397!
    13961398!*******************************************************************************
     
    20192021! In the implementation with 3 fields, the processes may have posted
    20202022! MPI_Irecv requests that should be cancelled here
    2021 !! TODO:
    20222023! if (.not.lmp_sync) then
    20232024!   r=mp_pid*nvar_async
     
    21052106!   
    21062107!
    2107 ! TODO
    21082108!
    21092109!*******************************************************************************
     
    21322132    uu(:,:,:,li:ui) = 10.0
    21332133    vv(:,:,:,li:ui) = 0.0
    2134     uupol(:,:,:,li:ui) = 10.0 ! TODO check if ok
     2134    uupol(:,:,:,li:ui) = 10.0
    21352135    vvpol(:,:,:,li:ui)=0.0
    21362136    ww(:,:,:,li:ui)=0.
     
    21642164    tropopause(:,:,:,li:ui)=10000.
    21652165    oli(:,:,:,li:ui)=0.01
    2166     z0=1.0
    21672166 
    21682167  end subroutine set_fields_synthetic
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG