Changeset b0434e1 in flexpart.git


Ignore:
Timestamp:
Feb 4, 2016, 9:38:22 AM (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:
db712a8
Parents:
9484483
Message:

Initial code to handle cloud water in nested wind fields (it is not completely implemented in this commit)

Location:
src
Files:
14 edited

Legend:

Unmodified
Added
Removed
  • src/FLEXPART.f90

    rfddc6ec rb0434e1  
    5656  ! Initialize arrays in com_mod
    5757  !*****************************
    58   call com_mod_allocate(maxpart)
    59 
     58  call com_mod_allocate_part(maxpart)
     59 
    6060
    6161  ! Generate a large number of random numbers
     
    171171  call readavailable
    172172
     173  ! If nested wind fields are used, allocate arrays
     174  !************************************************
     175
     176  if (verbosity.gt.0) then
     177    write(*,*) 'call com_mod_allocate_nests'
     178  endif
     179  call com_mod_allocate_nests
     180
    173181  ! Read the model grid specifications,
    174182  ! both for the mother domain and eventual nests
  • src/FLEXPART_MPI.f90

    rfddc6ec rb0434e1  
    6363! Initialize arrays in com_mod
    6464!*****************************
    65   call com_mod_allocate(maxpart_mpi)
     65  call com_mod_allocate_part(maxpart_mpi)
    6666
    6767  ! Generate a large number of random numbers
     
    195195  endif 
    196196  call readavailable
    197 !end if
     197
     198  ! If nested wind fields are used, allocate arrays
     199  !************************************************
     200
     201  if (verbosity.gt.0 .and. lroot) then
     202    write(*,*) 'call com_mod_allocate_nests'
     203  endif
     204  call com_mod_allocate_nests
    198205
    199206! Read the model grid specifications,
     
    445452! NIK 16.02.2005
    446453  if (lroot) then
    447     call MPI_Reduce(MPI_IN_PLACE, tot_blc_count, 1, MPI_INTEGER, MPI_SUM, id_root, &
     454    call MPI_Reduce(MPI_IN_PLACE, tot_blc_count, 1, MPI_INTEGER8, MPI_SUM, id_root, &
    448455         & mp_comm_used, mp_ierr)
    449     call MPI_Reduce(MPI_IN_PLACE, tot_inc_count, 1, MPI_INTEGER, MPI_SUM, id_root, &
     456    call MPI_Reduce(MPI_IN_PLACE, tot_inc_count, 1, MPI_INTEGER8, MPI_SUM, id_root, &
    450457         & mp_comm_used, mp_ierr)
    451458  else
    452459    if (mp_partgroup_pid.ge.0) then ! Skip for readwind process
    453       call MPI_Reduce(tot_blc_count, tot_blc_count, 1, MPI_INTEGER, MPI_SUM, id_root, &
     460      call MPI_Reduce(tot_blc_count, tot_blc_count, 1, MPI_INTEGER8, MPI_SUM, id_root, &
    454461           & mp_comm_used, mp_ierr)
    455       call MPI_Reduce(tot_inc_count, tot_inc_count, 1, MPI_INTEGER, MPI_SUM, id_root, &
     462      call MPI_Reduce(tot_inc_count, tot_inc_count, 1, MPI_INTEGER8, MPI_SUM, id_root, &
    456463           & mp_comm_used, mp_ierr)
    457464    end if
  • src/com_mod.f90

    rfddc6ec rb0434e1  
    138138
    139139!NIK 16.02.2015
    140   integer :: tot_blc_count=0, tot_inc_count=0
    141 
     140  integer(selected_int_kind(16)) :: tot_blc_count=0, tot_inc_count=0
    142141
    143142
     
    487486  !*****************
    488487
    489   real :: uun(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,maxnests)
    490   real :: vvn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,maxnests)
    491   real :: wwn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,maxnests)
    492   real :: ttn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,maxnests)
    493   real :: qvn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,maxnests)
    494   real :: pvn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,maxnests)
    495   integer(kind=1) :: cloudsn(0:nxmaxn-1,0:nymaxn-1,0:nzmax,numwfmem,maxnests)
    496   integer :: cloudsnh(0:nxmaxn-1,0:nymaxn-1,numwfmem,maxnests)
    497   real :: rhon(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,maxnests)
    498   real :: drhodzn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,maxnests)
    499   real :: tthn(0:nxmaxn-1,0:nymaxn-1,nuvzmax,numwfmem,maxnests)
    500   real :: qvhn(0:nxmaxn-1,0:nymaxn-1,nuvzmax,numwfmem,maxnests)
     488  real,allocatable,dimension(:,:,:,:,:) :: uun, vvn, wwn, ttn, qvn, pvn,&
     489       & rhon, drhodzn, tthn, qvhn
     490  integer,allocatable,dimension(:,:,:,:) :: cloudsnh
     491  integer(kind=1),allocatable,dimension(:,:,:,:,:) :: cloudsn
    501492
    502493  ! 2d nested fields
     
    752743  integer :: mpi_mode=0 ! .gt. 0 if running MPI version
    753744  logical :: lroot=.true. ! true if serial version, or if MPI .and. root process
    754 
    755   contains
    756       subroutine com_mod_allocate(nmpart)
    757 !*******************************************************************************   
    758 ! Dynamic allocation of arrays
    759 !
    760 ! For FLEXPART version 9.2 and earlier these arrays were statically declared
    761 ! with size maxpart. This function is introduced so that the MPI version
    762 ! can declare these arrays with smaller size ("maxpart per process"), while
    763 ! the serial version allocate at run-time with size maxpart
    764 !
    765 !*******************************************************************************
     745 
     746contains
     747  subroutine com_mod_allocate_part(nmpart)
     748  !*******************************************************************************   
     749  ! Dynamic allocation of arrays
     750  !
     751  ! For FLEXPART version 9.2 and earlier these arrays were statically declared
     752  ! with size maxpart. This function is introduced so that the MPI version
     753  ! can declare these arrays with smaller size ("maxpart per process"), while
     754  ! the serial version allocate at run-time with size maxpart
     755  !
     756  !*******************************************************************************
    766757    implicit none
    767758
     
    779770         & vs(nmpart),ws(nmpart),cbt(nmpart))
    780771   
    781   end subroutine com_mod_allocate
     772  end subroutine com_mod_allocate_part
     773
     774
     775  subroutine com_mod_allocate_nests
     776  !*******************************************************************************   
     777  ! Dynamic allocation of arrays
     778  !
     779  ! For nested wind fields.
     780  !
     781  !*******************************************************************************
     782    implicit none
     783
     784    allocate(uun(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,numbnests))
     785    allocate(vvn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,numbnests))
     786    allocate(wwn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,numbnests))
     787    allocate(ttn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,numbnests))
     788    allocate(qvn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,numbnests))
     789    allocate(pvn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,numbnests))
     790    allocate(cloudsn(0:nxmaxn-1,0:nymaxn-1,0:nzmax,numwfmem,numbnests))
     791    allocate(cloudsnh(0:nxmaxn-1,0:nymaxn-1,numwfmem,numbnests))
     792    allocate(rhon(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,numbnests))
     793    allocate(drhodzn(0:nxmaxn-1,0:nymaxn-1,nzmax,numwfmem,numbnests))
     794    allocate(tthn(0:nxmaxn-1,0:nymaxn-1,nuvzmax,numwfmem,numbnests))
     795    allocate(qvhn(0:nxmaxn-1,0:nymaxn-1,nuvzmax,numwfmem,numbnests))
     796
     797   
     798  end subroutine com_mod_allocate_nests
    782799   
    783800
  • src/ecmwf_mod.f90

    r6a678e3 rb0434e1  
    4949  !*********************************************
    5050
    51 !  integer,parameter :: maxnests=0,nxmaxn=351,nymaxn=351 !ECMWF
     51  integer,parameter :: maxnests=1,nxmaxn=361,nymaxn=181 !ECMWF
    5252
    5353
  • src/gfs_mod.f90

    r6a678e3 rb0434e1  
    4444  integer,parameter :: nxshift=0     ! for GFS or FNL
    4545
     46  integer,parameter :: maxnests=1,nxmaxn=361,nymaxn=181
    4647end module wind_mod
  • src/gridcheck.f90

    rfdc0f03 rb0434e1  
    104104  character(len=24) :: gribErrorMsg = 'Error reading grib file'
    105105  character(len=20) :: gribFunction = 'gridcheck'
    106 
    107   !NIK 16.02.2015
    108   tot_blc_count=0 !count for total number of occurences of below cloud scavenging
    109   tot_inc_count=0 !count for total number of occurences of in cloud scavenging
    110106
    111107
  • src/gridcheck_nests.f90

    r5f9d14a rb0434e1  
    170170  elseif ((parCat.eq.1).and.(parNum.eq.0).and.(typSurf.eq.105)) then ! Q
    171171    isec1(6)=133         ! indicatorOfParameter
     172  elseif ((parCat.eq.1).and.(parNum.eq.83).and.(typSurf.eq.105)) then ! clwc
     173    isec1(6)=246         ! indicatorOfParameter
     174    ! readclouds=.true.
     175    ! sumclouds=.false.
     176  elseif ((parCat.eq.1).and.(parNum.eq.84).and.(typSurf.eq.105)) then ! ciwc
     177    isec1(6)=247         ! indicatorOfParameter
     178!ZHG end
     179! ESO qc(=clwc+ciwc)
     180  elseif ((parCat.eq.201).and.(parNum.eq.31).and.(typSurf.eq.105)) then ! qc
     181    isec1(6)=201031      ! indicatorOfParameter
     182    ! readclouds=.true.
     183    ! sumclouds=.true.
    172184  elseif ((parCat.eq.3).and.(parNum.eq.0).and.(typSurf.eq.1)) then !SP
    173185    isec1(6)=134         ! indicatorOfParameter
  • src/makefile

    r6a678e3 rb0434e1  
    3939
    4040ifeq ($(gcc), 4.9)
    41 # Compiled libraries under users ~flexpart (or ~espen), gfortran v4.9
     41# Compiled libraries under users ~flexpart, gfortran v4.9
    4242        ROOT_DIR = /homevip/flexpart/
    4343#       ROOT_DIR = /homevip/espen/
     
    6363## OPTIMIZATION LEVEL
    6464O_LEV = 2 # [0,1,2,3,g,s,fast]
    65 O_LEV_DBG = 0 # [0,g]
     65O_LEV_DBG = g # [0,g]
    6666
    6767## LIBRARIES
    68 LIBS = -lgrib_api_f90 -lgrib_api -lm -ljasper -lnetcdff -llapack  # -fopenmp # -llapack
     68LIBS = -lgrib_api_f90 -lgrib_api -lm -ljasper -lnetcdff -llapack  # -fopenmp
    6969
    7070FFLAGS   = -I$(INCPATH1) -I$(INCPATH2) -O$(O_LEV) -g -m64 -mcmodel=medium -fconvert=little-endian -frecord-marker=4 -fmessage-length=0 -flto=jobserver -O$(O_LEV) $(FUSER) # -march=native
    7171
    72 DBGFLAGS = -I$(INCPATH1) -I$(INCPATH2) -O$(O_LEV_DBG) -g3 -ggdb3 -m64 -mcmodel=medium -fconvert=little-endian -frecord-marker=4 -fmessage-length=0 -flto=jobserver -O$(O_LEV_DBG) -fbacktrace -Warray-bounds  -Wall -fcheck=all $(FUSER)  #  -ffpe-trap=invalid,overflow,denormal,underflow,zero -fdump-core
     72DBGFLAGS = -I$(INCPATH1) -I$(INCPATH2) -O$(O_LEV_DBG) -g3 -ggdb3 -m64 -mcmodel=medium -fconvert=little-endian -frecord-marker=4 -fmessage-length=0 -flto=jobserver -O$(O_LEV_DBG) -fbacktrace   -Wall  -fdump-core $(FUSER)  #  -ffpe-trap=invalid,overflow,denormal,underflow,zero  -Warray-bounds -fcheck=all
    7373
    7474LDFLAGS  = $(FFLAGS) -L$(LIBPATH1) $(LIBS) #-L$(LIBPATH2)
  • src/par_mod.f90

    r26f6039 rb0434e1  
    172172
    173173  !integer,parameter :: maxnests=0, nxmaxn=0, nymaxn=0
    174   integer,parameter :: maxnests=0,nxmaxn=351,nymaxn=351 !ECMWF
     174  !integer,parameter :: maxnests=0,nxmaxn=351,nymaxn=351 !ECMWF
    175175
    176176  !integer,parameter :: maxnests=1, nxmaxn=201, nymaxn=161 ! FNL XF
  • src/readreleases.f90

    r0f20c31 rb0434e1  
    225225  if (stat.ne.0) write(*,*)'ERROR: could not allocate specnum_rel2'
    226226  specnum_rel2=specnum_rel(1:nspec)
    227   deallocate(specnum_rel)
     227  deallocate(specnum_rel)
     228! eso: BUG, crashes here for nspec=12 and maxspec=6,
     229! TODO: catch error and exit
    228230  allocate(specnum_rel(nspec),stat=stat)
    229231  if (stat.ne.0) write(*,*)'ERROR: could not allocate specnum_rel'
  • src/readwind.f90

    r41d8574 rb0434e1  
    190190    elseif ((parCat.eq.1).and.(parNum.eq.0).and.(typSurf.eq.105)) then ! Q
    191191      isec1(6)=133         ! indicatorOfParameter
    192 ! ESO Cloud water is in a) fields CLWC and CIWC, *or* b) field qc
     192! ESO Cloud water is in a) fields CLWC and CIWC, *or* b) field QC
    193193    elseif ((parCat.eq.1).and.(parNum.eq.83).and.(typSurf.eq.105)) then ! clwc
    194194      isec1(6)=246         ! indicatorOfParameter
     
    377377        readclouds=.true.
    378378        sumclouds=.true.
    379 !if (clwch(i,j,nlev_ec-k+2,n) .gt. 0)        write(*,*) 'readwind: found water!', clwch(i,j,nlev_ec-k+2,n)
    380379      endif
    381380
  • src/readwind_nests.f90

    r8a65cb0 rb0434e1  
    173173  elseif ((parCat.eq.1).and.(parNum.eq.0).and.(typSurf.eq.105)) then ! Q
    174174    isec1(6)=133         ! indicatorOfParameter
     175! ESO Cloud water is in a) fields CLWC and CIWC, *or* b) field QC
     176    elseif ((parCat.eq.1).and.(parNum.eq.83).and.(typSurf.eq.105)) then ! clwc
     177      isec1(6)=246         ! indicatorOfParameter
     178    elseif ((parCat.eq.1).and.(parNum.eq.84).and.(typSurf.eq.105)) then ! ciwc
     179      isec1(6)=247         ! indicatorOfParameter
     180! ESO qc(=clwc+ciwc):
     181    elseif ((parCat.eq.201).and.(parNum.eq.31).and.(typSurf.eq.105)) then ! qc
     182      isec1(6)=201031         ! indicatorOfParameter
    175183  elseif ((parCat.eq.3).and.(parNum.eq.0).and.(typSurf.eq.1)) then !SP
    176184    isec1(6)=134         ! indicatorOfParameter
     
    203211  elseif ((parCat.eq.4).and.(parNum.eq.9).and.(typSurf.eq.1)) then ! SR
    204212    isec1(6)=176         ! indicatorOfParameter
    205   elseif ((parCat.eq.2).and.(parNum.eq.17) .or. parId .eq. 180) then ! EWSS !added by mc to make it consisitent with new readwind.f90
     213  elseif ((parCat.eq.2).and.(parNum.eq.38) .or. parId .eq. 180) then ! EWSS !added by mc to make it consisitent with new readwind.f90
    206214    isec1(6)=180         ! indicatorOfParameter
    207   elseif ((parCat.eq.2).and.(parNum.eq.18) .or. parId .eq. 181) then ! NSSS !added by mc to make it consisitent with new readwind.f90
     215  elseif ((parCat.eq.2).and.(parNum.eq.37) .or. parId .eq. 181) then ! NSSS !added by mc to make it consisitent with new readwind.f90
    208216    isec1(6)=181         ! indicatorOfParameter
    209217  elseif ((parCat.eq.3).and.(parNum.eq.4)) then ! ORO
     
    335343        if(isec1(6).eq.131) iumax=max(iumax,nlev_ec-k+1)
    336344        if(isec1(6).eq.135) iwmax=max(iwmax,nlev_ec-k+1)
     345
     346! ESO TODO:
     347! -add check for if one of clwc/ciwc missing (error),
     348!    also if all 3 cw fields present, use qc and disregard the others
     349! -use same flags readclouds/sumclouds as in mother grid? this assumes
     350!    that both the nested and mother grids contain CW in same format
     351        if(isec1(6).eq.246) then  !! CLWC  Cloud liquid water content [kg/kg]
     352          clwch(i,j,nlev_ec-k+2,n)=zsec4(nxfield*(ny-j-1)+i+1)
     353          ! readclouds=.true.
     354          ! sumclouds=.false.
     355        endif
     356        if(isec1(6).eq.247) then  !! CIWC  Cloud ice water content
     357          ciwch(i,j,nlev_ec-k+2,n)=zsec4(nxfield*(ny-j-1)+i+1)
     358        endif
     359!ZHG end
     360!ESO read qc (=clwc+ciwc)
     361        if(isec1(6).eq.201031) then  !! QC  Cloud liquid water content [kg/kg]
     362          clwch(i,j,nlev_ec-k+2,n)=zsec4(nxfield*(ny-j-1)+i+1)
     363          ! readclouds=.true.
     364          ! sumclouds=.true.
     365        endif
     366
    337367
    338368      end do
  • src/verttransform.f90

    r26f6039 rb0434e1  
    578578! to include future cloud processing by non-precipitating-clouds.
    579579!***********************************************************************************
    580     write(*,*) 'using cloud water from ECMWF'
     580    write(*,*) 'Global ECMWF fields: using cloud water'
    581581    clw(:,:,:,n)=0.0
    582582    icloud_stats(:,:,:,n)=0.0
     
    635635      end do
    636636    end do
     637
     638! eso: copy the relevant data to clw4 to reduce amount of communicated data for MPI
     639    clw4(:,:,n) = icloud_stats(:,:,4,n)
     640
    637641!**************************************************************************
    638642  else       ! use old definitions
     
    640644!   create a cloud and rainout/washout field, clouds occur where rh>80%
    641645!   total cloudheight is stored at level 0
    642     write(*,*) 'using cloud water from Parameterization'
     646    write(*,*) 'Global fields: using cloud water from Parameterization'
    643647    do jy=0,nymin1
    644648      do ix=0,nxmin1
     
    681685  endif !readclouds
    682686
    683 ! eso: copy the relevant data to clw4 to reduce amount of communicated data for MPI
    684   clw4(:,:,n) = icloud_stats(:,:,4,n)
    685687
    686688     !********* TEST ***************
  • src/verttransform_nests.f90

    r4fbe7a5 rb0434e1  
    282282  !write (*,*) 'initializing nested cloudsn, n:',n
    283283  !   create a cloud and rainout/washout field, cloudsn occur where rh>80%
     284  write(*,*) 'Nested fields: using cloud water from Parameterization'
    284285  do jy=0,nyn(l)-1
    285286    do ix=0,nxn(l)-1
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG