Changeset 30 for trunk/src/FLEXPART.f90


Ignore:
Timestamp:
Oct 21, 2014, 8:08:00 AM (10 years ago)
Author:
hasod
Message:

ADD: Optional (compressed) netcdf output added. Activated via COMMAND
file. During compile time switches -DNETCDF_OUTPUT -cpp need to be
invoked. Compliation and linking is shown in makefile.netcdf

File:
1 edited

Legend:

Unmodified
Added
Removed
  • trunk/src/FLEXPART.f90

    r27 r30  
    4545  use conv_mod
    4646
     47#ifdef NETCDF_OUTPUT
     48  use netcdf_output_mod, only: writeheader_netcdf
     49#endif
     50
     51
    4752  implicit none
    4853
     
    303308  !******************************************************************
    304309
     310  if (lnetcdfout.eq.1) then
     311#ifdef NETCDF_OUTPUT
     312    call writeheader_netcdf(lnest = .false.)
     313#endif
     314  else
     315    call writeheader
     316  end if
     317
     318  if (nested_output.eq.1) then
     319    if (lnetcdfout.eq.1) then
     320#ifdef NETCDF_OUTPUT
     321      call writeheader_netcdf(lnest = .true.)
     322#endif
     323    else
     324      call writeheader_nest
     325    endif
     326  endif
     327
    305328  if (verbosity.gt.0) then
    306329    print*,'call writeheader'
     
    315338  if (nested_output.ne.1.and.surf_only.eq.1) call writeheader_surf
    316339
    317   !open(unitdates,file=path(2)(1:length(2))//'dates')
     340  if (lnetcdfout.ne.1) then
     341    open(unitdates,file=path(2)(1:length(2))//'dates')
     342  end if
    318343
    319344  if (verbosity.gt.0) then
     
    359384  if (verbosity.gt.0) then
    360385     if (verbosity.gt.1) then   
    361        CALL SYSTEM_CLOCK(count_clock, count_rate, count_max)
    362        write(*,*) 'SYSTEM_CLOCK',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
     386       call system_clock(count_clock, count_rate, count_max)
     387       write(*,*) 'System clock',(count_clock - count_clock0)/real(count_rate) !, count_rate, count_max
    363388     endif
    364389     if (info_flag.eq.1) then
    365        print*, 'info only mode (stop)'   
     390       print*, 'Info only mode (stop)'   
    366391       stop
    367392     endif
     
    373398  write(*,*) 'CONGRATULATIONS: YOU HAVE SUCCESSFULLY COMPLETED A FLEXPART MODEL RUN!'
    374399
     400  ! output wall time
     401  if (verbosity .gt. 0) then
     402    call system_clock(count_clock,count_rate)
     403    tins=(count_clock - count_clock0)/real(count_rate)
     404    print*,'Wall time ',tins,'s, ',tins/60,'min, ',tins/3600,'h.'
     405  endif
     406
    375407end program flexpart
Note: See TracChangeset for help on using the changeset viewer.
hosted by ZAMG