New URL for NEMO forge!   http://forge.nemo-ocean.eu

Since March 2022 along with NEMO 4.2 release, the code development moved to a self-hosted GitLab.
This present forge is now archived and remained online for history.
Changeset 7398 for branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC – NEMO

Ignore:
Timestamp:
2016-11-30T15:44:11+01:00 (7 years ago)
Author:
cbricaud
Message:

coarsening branch: first implementation of coarsening in PISCES

Location:
branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC
Files:
25 edited

Legend:

Unmodified
Added
Removed
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zbio.F90

    r7256 r7398  
    1515   !!---------------------------------------------------------------------- 
    1616   USE oce_trc         !  shared variables between ocean and passive tracers 
    17    USE trc             !  passive tracers common variables  
    1817   USE sms_pisces      !  PISCES Source Minus Sink variables 
    1918   USE p4zsink         !  vertical flux of particulate matter due to sinking 
     
    2625   USE p4zrem          !  Remineralisation of organic matter 
    2726   USE p4zfechem 
    28    USE prtctl_trc      !  print control for debugging 
    29    USE iom             !  I/O manager 
    30    
     27   USE prtctl_trc, ONLY: prt_ctl_trc_info,prt_ctl_trc !  print control for debugging 
     28  
    3129   IMPLICIT NONE 
    3230   PRIVATE 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zche.F90

    r7256 r7398  
    1919   !!---------------------------------------------------------------------- 
    2020   USE oce_trc       !  shared variables between ocean and passive tracers 
    21    USE trc           !  passive tracers common variables 
    2221   USE sms_pisces    !  PISCES Source Minus Sink variables 
    2322   USE lib_mpp       !  MPP library 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zfechem.F90

    r5602 r7398  
    1616   !!---------------------------------------------------------------------- 
    1717   USE oce_trc         !  shared variables between ocean and passive tracers 
    18    USE trc             !  passive tracers common variables  
    1918   USE sms_pisces      !  PISCES Source Minus Sink variables 
    2019   USE p4zopt          !  optical model 
    2120   USE p4zche          !  chemical model 
    2221   USE p4zsbc          !  Boundary conditions from sediments 
    23    USE prtctl_trc      !  print control for debugging 
    24    USE iom             !  I/O manager 
     22   USE prtctl_trc, ONLY : prt_ctl_trc_info,prt_ctl_trc      !  print control for debugging 
    2523 
    2624   IMPLICIT NONE 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zflx.F90

    r7256 r7398  
    2020   !!---------------------------------------------------------------------- 
    2121   USE oce_trc                      !  shared variables between ocean and passive tracers  
    22    USE trc                          !  passive tracers common variables 
    2322   USE sms_pisces                   !  PISCES Source Minus Sink variables 
    2423   USE p4zche                       !  Chemical model 
    25    USE prtctl_trc                   !  print control for debugging 
    26    USE iom                          !  I/O manager 
     24   USE prtctl_trc , ONLY : prt_ctl_trc_info,prt_ctl_trc !  print control for debugging 
    2725   USE fldread                      !  read input fields 
    2826#if defined key_cpl_carbon_cycle 
     
    198196            oce_co2(ji,jj) = ( zfld - zflu ) * rfact2 * e1e2t(ji,jj) * tmask(ji,jj,1) * 1000. 
    199197            ! compute the trend 
     198#if defined key_crs 
     199            tra(ji,jj,1,jpdic) = tra(ji,jj,1,jpdic) + ( zfld - zflu ) * rfact2 / e3t_max_crs(ji,jj,1) 
     200#else 
    200201            tra(ji,jj,1,jpdic) = tra(ji,jj,1,jpdic) + ( zfld - zflu ) * rfact2 / fse3t(ji,jj,1) * tmask(ji,jj,1) 
     202#endif 
    201203 
    202204            ! Compute O2 flux  
     
    204206            zflu16 = trb(ji,jj,1,jpoxy) * zkgo2(ji,jj) 
    205207            zoflx(ji,jj) = ( zfld16 - zflu16 ) * tmask(ji,jj,1) 
     208#if defined key_crs 
     209            tra(ji,jj,1,jpoxy) = tra(ji,jj,1,jpoxy) + zoflx(ji,jj) * rfact2 / e3t_max_crs(ji,jj,1) 
     210#else 
    206211            tra(ji,jj,1,jpoxy) = tra(ji,jj,1,jpoxy) + zoflx(ji,jj) * rfact2 / fse3t(ji,jj,1) 
     212#endif 
    207213         END DO 
    208214      END DO 
     
    212218!      t_atm_co2_flx     = glob_sum( satmco2(:,:) * e1e2t(:,:) )       ! Total atmospheric pCO2 
    213219      t_atm_co2_flx     =  atcco2      ! Total atmospheric pCO2 
    214   
     220 
     221#if ! defined key_crs  
    215222      IF(ln_ctl)   THEN  ! print mean trends (used for debugging) 
    216223         WRITE(charout, FMT="('flx ')") 
     
    218225         CALL prt_ctl_trc(tab4d=tra, mask=tmask, clinfo=ctrcnm) 
    219226      ENDIF 
     227#endif 
    220228 
    221229      IF( lk_iomput .AND. knt == nrdttrc ) THEN 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zint.F90

    r7256 r7398  
    1414   !!---------------------------------------------------------------------- 
    1515   USE oce_trc         !  shared variables between ocean and passive tracers 
    16    USE trc             !  passive tracers common variables  
    1716   USE sms_pisces      !  PISCES Source Minus Sink variables 
    18    USE iom 
    1917 
    2018   IMPLICIT NONE 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zlim.F90

    r7256 r7398  
    1616   !!---------------------------------------------------------------------- 
    1717   USE oce_trc         ! Shared ocean-passive tracers variables 
    18    USE trc             ! Tracers defined 
    1918   USE sms_pisces      ! PISCES variables 
    2019   USE p4zopt          ! Optical 
    21    USE iom             !  I/O manager 
    2220 
    2321   IMPLICIT NONE 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zlys.F90

    r7256 r7398  
    2020   !!---------------------------------------------------------------------- 
    2121   USE oce_trc         !  shared variables between ocean and passive tracers 
    22    USE trc             !  passive tracers common variables  
    2322   USE sms_pisces      !  PISCES Source Minus Sink variables 
    24    USE prtctl_trc      !  print control for debugging 
    25    USE iom             !  I/O manager 
     23   USE prtctl_trc,ONLY : prt_ctl_trc_info,prt_ctl_trc !  print control for debugging 
    2624 
    2725   IMPLICIT NONE 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zmeso.F90

    r7256 r7398  
    1616   !!---------------------------------------------------------------------- 
    1717   USE oce_trc         !  shared variables between ocean and passive tracers 
    18    USE trc             !  passive tracers common variables  
    1918   USE sms_pisces      !  PISCES Source Minus Sink variables 
    2019   USE p4zsink         !  vertical flux of particulate matter due to sinking 
    2120   USE p4zint          !  interpolation and computation of various fields 
    2221   USE p4zprod         !  production 
    23    USE prtctl_trc      !  print control for debugging 
    24    USE iom             !  I/O manager 
     22   USE prtctl_trc ,ONLY: prt_ctl_trc_info,prt_ctl_trc      !  print control for debugging 
    2523 
    2624   IMPLICIT NONE 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zmicro.F90

    r7256 r7398  
    1616   !!---------------------------------------------------------------------- 
    1717   USE oce_trc         !  shared variables between ocean and passive tracers 
    18    USE trc             !  passive tracers common variables  
    1918   USE sms_pisces      !  PISCES Source Minus Sink variables 
    2019   USE p4zlim          !  Co-limitations 
     
    2221   USE p4zint          !  interpolation and computation of various fields 
    2322   USE p4zprod         !  production 
    24    USE iom             !  I/O manager 
    25    USE prtctl_trc      !  print control for debugging 
     23   USE prtctl_trc, ONLY: prt_ctl_trc_info,prt_ctl_trc      !  print control for debugging 
    2624 
    2725   IMPLICIT NONE 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zmort.F90

    r7256 r7398  
    1515   !!---------------------------------------------------------------------- 
    1616   USE oce_trc         !  shared variables between ocean and passive tracers 
    17    USE trc             !  passive tracers common variables  
    1817   USE sms_pisces      !  PISCES Source Minus Sink variables 
    1918   USE p4zsink         !  vertical flux of particulate matter due to sinking 
    2019   USE p4zprod         !  Primary productivity  
    21    USE prtctl_trc      !  print control for debugging 
     20   USE prtctl_trc,ONLY: prt_ctl_trc_info,prt_ctl_trc      !  print control for debugging 
    2221 
    2322   IMPLICIT NONE 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zopt.F90

    r7256 r7398  
    1515   !!   p4z_opt       : light availability in the water column 
    1616   !!---------------------------------------------------------------------- 
    17    USE trc            ! tracer variables 
    1817   USE oce_trc        ! tracer-ocean share variables 
    1918   USE sms_pisces     ! Source Minus Sink of PISCES 
    20    USE iom            ! I/O manager 
    2119   USE fldread         !  time interpolation 
    22    USE prtctl_trc      !  print control for debugging 
    23  
     20   USE prtctl_trc,ONLY:prt_ctl_trc_info,prt_ctl_trc      !  print control for debugging 
     21   USE trc_oce, ONLY : trc_oce_rgb 
    2422 
    2523   IMPLICIT NONE 
     
    7674      REAL(wp) ::   zchl 
    7775      REAL(wp) ::   zc0 , zc1 , zc2, zc3, z1_dep 
     76      REAL(wp) ::   zfse3 
    7877      REAL(wp), POINTER, DIMENSION(:,:  ) :: zdepmoy, zetmp1, zetmp2, zetmp3, zetmp4 
    7978      REAL(wp), POINTER, DIMENSION(:,:  ) :: zqsr100, zqsr_corr 
     
    108107               ekg(ji,jj,jk) = xkrgb(2,irgb) * fse3t(ji,jj,jk) 
    109108               ekr(ji,jj,jk) = xkrgb(3,irgb) * fse3t(ji,jj,jk) 
     109!#if defined key_crs 
     110!               zfse3 = e3t_max_crs(ji,jj,jk) 
     111!#else 
     112!               zfse3 = fse3t(ji,jj,jk) 
     113!#endif 
     114!               ekb(ji,jj,jk) = xkrgb(1,irgb) * zfse3 
     115!               ekg(ji,jj,jk) = xkrgb(2,irgb) * zfse3 
     116!               ekr(ji,jj,jk) = xkrgb(3,irgb) * zfse3 
    110117            END DO 
    111118         END DO 
     
    193200                  zetmp4 (ji,jj) = zetmp4 (ji,jj) + ediat    (ji,jj,jk) * fse3t(ji,jj,jk) ! production 
    194201                  zdepmoy(ji,jj) = zdepmoy(ji,jj) + fse3t(ji,jj,jk) 
     202!#if defined key_crs 
     203!                zfse3 = e3t_max_crs(ji,jj,jk) 
     204!#else 
     205!               zfse3 = fse3t(ji,jj,jk) 
     206!#endif 
     207!                  zetmp1 (ji,jj) = zetmp1 (ji,jj) + etot     (ji,jj,jk) * zfse3 ! remineralisation 
     208!                  zetmp2 (ji,jj) = zetmp2 (ji,jj) + etot_ndcy(ji,jj,jk) * zfse3 ! production 
     209!                  zetmp3 (ji,jj) = zetmp3 (ji,jj) + enano    (ji,jj,jk) * zfse3 ! production 
     210!                  zetmp4 (ji,jj) = zetmp4 (ji,jj) + ediat    (ji,jj,jk) * zfse3 ! production 
     211!                  zdepmoy(ji,jj) = zdepmoy(ji,jj) + zfse3 
    195212               ENDIF 
    196213            END DO 
     
    254271      !! * local variables 
    255272      INTEGER    ::   ji, jj, jk     ! dummy loop indices 
    256       REAL(wp), DIMENSION(jpi,jpj)     ::  zqsr          !   shortwave 
    257       !!---------------------------------------------------------------------- 
     273      REAL(wp), POINTER, DIMENSION(:,:)     ::  zqsr          !   shortwave 
     274      !!---------------------------------------------------------------------- 
     275      CALL wrk_alloc( jpi, jpj, zqsr ) 
    258276 
    259277      !  Real shortwave 
     
    306324        ! 
    307325      ENDIF 
    308       !  
     326      ! 
     327      CALL wrk_dealloc( jpi, jpj, zqsr ) 
     328      ! 
    309329   END SUBROUTINE p4z_opt_par 
    310330 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zprod.F90

    r7256 r7398  
    1717   !!---------------------------------------------------------------------- 
    1818   USE oce_trc         !  shared variables between ocean and passive tracers 
    19    USE trc            !  passive tracers common variables  
     19   USE trc, ONLY: cvol !  passive tracers common variables  
    2020   USE sms_pisces      !  PISCES Source Minus Sink variables 
    2121   USE p4zopt          !  optical model 
    2222   USE p4zlim          !  Co-limitations of differents nutrients 
    23    USE prtctl_trc      !  print control for debugging 
    24    USE iom             !  I/O manager 
     23   USE prtctl_trc, ONLY: prt_ctl_trc_info,prt_ctl_trc     !  print control for debugging 
    2524 
    2625   IMPLICIT NONE 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zrem.F90

    r7256 r7398  
    1818   !!---------------------------------------------------------------------- 
    1919   USE oce_trc         !  shared variables between ocean and passive tracers 
    20    USE trc             !  passive tracers common variables  
    2120   USE sms_pisces      !  PISCES Source Minus Sink variables 
    2221   USE p4zopt          !  optical model 
     
    2625   USE p4zint          !  interpolation and computation of various fields 
    2726   USE p4zlim 
    28    USE prtctl_trc      !  print control for debugging 
    29    USE iom             !  I/O manager 
     27   USE prtctl_trc, ONLY: prt_ctl_trc_info,prt_ctl_trc    !  print control for debugging 
    3028 
    3129 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zsbc.F90

    r7256 r7398  
    1414   !!---------------------------------------------------------------------- 
    1515   USE oce_trc         !  shared variables between ocean and passive tracers 
    16    USE trc             !  passive tracers common variables  
    1716   USE sms_pisces      !  PISCES Source Minus Sink variables 
    18    USE iom             !  I/O manager 
    1917   USE fldread         !  time interpolation 
    2018 
     
    161159             zcoef = rno3 * 14E6 * ryyss 
    162160             CALL fld_read( kt, 1, sf_ndepo ) 
     161#if defined key_crs 
     162             nitdep(:,:) = sf_ndepo(1)%fnow(:,:,1) / zcoef / e3t_max_crs(:,:,1)  
     163#else 
    163164             nitdep(:,:) = sf_ndepo(1)%fnow(:,:,1) / zcoef / fse3t(:,:,1)  
     165#endif 
    164166         ENDIF 
    165167         IF( lk_vvl ) THEN 
    166168           zcoef = rno3 * 14E6 * ryyss 
     169#if defined key_crs 
     170           nitdep(:,:) = sf_ndepo(1)%fnow(:,:,1) / zcoef / e3t_max_crs(:,:,1)  
     171#else 
    167172           nitdep(:,:) = sf_ndepo(1)%fnow(:,:,1) / zcoef / fse3t(:,:,1)  
     173#endif 
    168174         ENDIF 
    169175      ENDIF 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zsed.F90

    r7256 r7398  
    1616   !!---------------------------------------------------------------------- 
    1717   USE oce_trc         !  shared variables between ocean and passive tracers 
    18    USE trc             !  passive tracers common variables  
    1918   USE sms_pisces      !  PISCES Source Minus Sink variables 
    2019   USE p4zsink         !  vertical flux of particulate matter due to sinking 
     
    2322   USE p4zsbc          !  External source of nutrients  
    2423   USE p4zint          !  interpolation and computation of various fields 
    25    USE iom             !  I/O manager 
    26    USE prtctl_trc      !  print control for debugging 
     24   USE prtctl_trc, ONLY: prt_ctl_trc_info,prt_ctl_trc     !  print control for debugging 
    2725 
    2826   IMPLICIT NONE 
     
    105103         DO jj = 1, jpj 
    106104            DO ji = 1, jpi 
     105#if defined key_crs 
     106               zdep    = rfact2 / e3t_max_crs(ji,jj,1) 
     107#else 
    107108               zdep    = rfact2 / fse3t(ji,jj,1) 
     109#endif 
    108110               zwflux  = fmmflx(ji,jj) / 1000._wp 
    109111               zfminus = MIN( 0._wp, -zwflux ) * trb(ji,jj,1,jpfer) * zdep 
     
    129131         CALL wrk_alloc( jpi, jpj, jpk, zirondep      ) 
    130132         !                                              ! Iron and Si deposition at the surface 
     133#if defined key_crs 
     134         IF( ln_solub ) THEN 
     135            zirondep(:,:,1) = solub(:,:) * dust(:,:) * mfrac * rfact2 / e3t_max_crs(:,:,1) / 55.85 + 3.e-10 * r1_ryyss 
     136         ELSE 
     137            zirondep(:,:,1) = dustsolub  * dust(:,:) * mfrac * rfact2 / e3t_max_crs(:,:,1) / 55.85 + 3.e-10 * r1_ryyss 
     138         ENDIF 
     139         zsidep(:,:) = 8.8 * 0.075 * dust(:,:) * mfrac * rfact2 / e3t_max_crs(:,:,1) / 28.1 
     140         zpdep (:,:) = 0.1 * 0.021 * dust(:,:) * mfrac * rfact2 / e3t_max_crs(:,:,1) / 31. / po4r 
     141#else 
    131142         IF( ln_solub ) THEN 
    132143            zirondep(:,:,1) = solub(:,:) * dust(:,:) * mfrac * rfact2 / fse3t(:,:,1) / 55.85 + 3.e-10 * r1_ryyss  
     
    136147         zsidep(:,:) = 8.8 * 0.075 * dust(:,:) * mfrac * rfact2 / fse3t(:,:,1) / 28.1  
    137148         zpdep (:,:) = 0.1 * 0.021 * dust(:,:) * mfrac * rfact2 / fse3t(:,:,1) / 31. / po4r  
     149#endif 
    138150         !                                              ! Iron solubilization of particles in the water column 
    139151         !                                              ! dust in kg/m2/s ---> 1/55.85 to put in mol/Fe ;  wdust in m/j 
     
    211223         DO ji = 1, jpi 
    212224            ikt  = mbkt(ji,jj) 
     225!#if defined key_crs 
     226!            zdep = e3t_max_crs(ji,jj,ikt) / xstep 
     227!#else 
     228!            zdep = fse3t(ji,jj,ikt) / xstep 
     229!#endif 
    213230            zdep = fse3t(ji,jj,ikt) / xstep 
    214231            zwsbio4(ji,jj) = MIN( 0.99 * zdep, wsbio4(ji,jj,ikt) ) 
     
    284301         DO ji = 1, jpi 
    285302            ikt  = mbkt(ji,jj) 
    286             zdep = xstep / fse3t(ji,jj,ikt)  
     303#if defined key_crs 
     304            zdep = xstep / e3t_max_crs(ji,jj,ikt) 
     305#else 
     306            zdep = xstep / fse3t(ji,jj,ikt) 
     307#endif 
    287308            zws4 = zwsbio4(ji,jj) * zdep 
    288309            zwsc = zwscal (ji,jj) * zdep 
     
    312333         DO ji = 1, jpi 
    313334            ikt  = mbkt(ji,jj) 
    314             zdep = xstep / fse3t(ji,jj,ikt)  
     335#if defined key_crs 
     336            zdep = xstep / e3t_max_crs(ji,jj,ikt) 
     337#else 
     338            zdep = xstep / fse3t(ji,jj,ikt) 
     339#endif 
    315340            zws4 = zwsbio4(ji,jj) * zdep 
    316341            zws3 = zwsbio3(ji,jj) * zdep 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zsink.F90

    r7256 r7398  
    1616   !!---------------------------------------------------------------------- 
    1717   USE oce_trc         !  shared variables between ocean and passive tracers 
    18    USE trc             !  passive tracers common variables  
    1918   USE sms_pisces      !  PISCES Source Minus Sink variables 
    20    USE prtctl_trc      !  print control for debugging 
    21    USE iom             !  I/O manager 
    22    USE lib_mpp 
     19   USE prtctl_trc, ONLY: prt_ctl_trc_info,prt_ctl_trc      !  print control for debugging 
     20   USE lib_mpp, ONLY: mpp_max 
    2321 
    2422   IMPLICIT NONE 
     
    137135             DO ji = 1, jpi 
    138136                IF( tmask(ji,jj,jk) == 1) THEN 
     137!#if defined key_crs 
     138!                   zwsmax =  0.5 * e3t_max_crs(ji,jj,jk) / xstep 
     139!#else 
     140!                   zwsmax =  0.5 * fse3t(ji,jj,jk) / xstep 
     141!#endif 
    139142                   zwsmax =  0.5 * fse3t(ji,jj,jk) / xstep 
    140143                   iiter1 =  MAX( iiter1, INT( wsbio3(ji,jj,jk) / zwsmax ) ) 
     
    156159            DO ji = 1, jpi 
    157160               IF( tmask(ji,jj,jk) == 1 ) THEN 
     161!#if defined key_crs 
     162!                   zwsmax =  0.5 * e3t_max_crs(ji,jj,jk) / xstep 
     163!#else 
     164!                   zwsmax =  0.5 * fse3t(ji,jj,jk) / xstep 
     165!#endif 
    158166                 zwsmax = 0.5 * fse3t(ji,jj,jk) / xstep 
    159167                 wsbio3(ji,jj,jk) = MIN( wsbio3(ji,jj,jk), zwsmax * FLOAT( iiter1 ) ) 
     
    844852            DO jj = 1, jpj       
    845853               DO ji = 1, jpi     
     854#if defined key_crs 
     855                  zigma = zwsink2(ji,jj,jk+1) * zstep / e3w_max_crs(ji,jj,jk+1) 
     856#else 
    846857                  zigma = zwsink2(ji,jj,jk+1) * zstep / fse3w(ji,jj,jk+1) 
     858#endif 
    847859                  zew   = zwsink2(ji,jj,jk+1) 
    848860                  psinkflx(ji,jj,jk+1) = -zew * ( trb(ji,jj,jk,jp_tra) - 0.5 * ( 1 + zigma ) * zakz(ji,jj,jk) ) * zstep 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zsms.F90

    r7256 r7398  
    1414   !!---------------------------------------------------------------------- 
    1515   USE oce_trc         !  shared variables between ocean and passive tracers 
    16    USE trc             !  passive tracers common variables  
    1716   USE trcdta 
    1817   USE sms_pisces      !  PISCES Source Minus Sink variables 
     
    2524   USE p4zint          !  time interpolation 
    2625   USE p4zrem          !  remineralisation 
    27    USE iom             !  I/O manager 
    2826   USE trd_oce         !  Ocean trends variables 
    2927   USE trdtrc          !  TOP trends variables 
    3028   USE sedmodel        !  Sediment model 
    31    USE prtctl_trc      !  print control for debugging 
     29   USE prtctl_trc, ONLY:prt_ctl_trc_info,prt_ctl_trc     !  print control for debugging 
    3230 
    3331   IMPLICIT NONE 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/PISCES/trcice_pisces.F90

    r7256 r7398  
    1717   USE par_pisces      ! PISCES parameters 
    1818   USE oce_trc         ! Shared variables between ocean and passive tracers 
    19    USE trc             ! Passive tracers common variables  
    2019   USE phycst          ! Ocean physics parameters 
    2120   USE sms_pisces      ! PISCES Source Minus Sink variables 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/PISCES/trcwri_pisces.F90

    r4996 r7398  
    1212   !! trc_wri_pisces   :  outputs of concentration fields 
    1313   !!---------------------------------------------------------------------- 
    14    USE trc         ! passive tracers common variables  
    1514   USE sms_pisces  ! PISCES variables 
    16    USE iom         ! I/O manager 
     15   USE trc, ONLY: ctrcnm,trn         ! passive tracers common variables  
     16   USE sms_pisces                    ! PISCES variables 
     17   USE iom, ONLY : iom_swap, iom_put,iom_use ! I/O manager 
     18   USE crs, ONLY : ln_crs_top 
     19   USE oce_trc 
    1720 
    1821   IMPLICIT NONE 
     
    3538      REAL(wp), DIMENSION(jpi,jpj) :: zdic, zo2min, zdepo2min 
    3639      !!--------------------------------------------------------------------- 
     40      IF( ln_crs_top ) CALL iom_swap( "nemo_crs" ) 
    3741  
    3842      ! write the tracer concentrations in the file 
     
    8286#endif 
    8387      ! 
     88      IF( ln_crs_top ) CALL iom_swap( "nemo" ) 
     89      ! 
    8490   END SUBROUTINE trc_wri_pisces 
    8591 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/TRP/trcrad.F90

    r4990 r7398  
    1414   !!---------------------------------------------------------------------- 
    1515   USE oce_trc             ! ocean dynamics and tracers variables 
    16    USE trc                 ! ocean passive tracers variables 
     16   USE trc, ONLY: cvol     ! ocean passive tracers variables 
    1717   USE trd_oce 
    1818   USE trdtra 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/oce_trc.F90

    r7332 r7398  
    88   !!---------------------------------------------------------------------- 
    99#if defined key_top 
     10   USE dom_oce    , ONLY : ndastp 
     11   USE dom_oce    , ONLY : nyear_len,nday,nyear,nday_year 
     12   USE dom_oce    , ONLY : gdepw_1d 
     13   USE dom_oce    , ONLY : rdttra 
     14   USE dom_oce    , ONLY : Agrif_Root      => Agrif_Root 
     15   USE sbc_oce    , ONLY : nn_ice_embd 
     16   USE sbc_oce    , ONLY : ln_cpl 
     17   USE sbc_oce    , ONLY : ln_rnf 
     18   USE sbc_oce    , ONLY : ncpl_qsr_freq 
     19 
     20   USE traqsr     , ONLY : ln_qsr_bio =>    ln_qsr_bio 
     21   USE traqsr     , ONLY : rn_si0     =>    rn_si0     !: very near surface depth of extinction 
     22   USE traqsr     , ONLY : rn_abs     =>    rn_abs     !: fraction absorbed in the very near surface 
     23 
     24   USE iom        , ONLY : iom_open , iom_get , iom_varid , iom_rstput , iom_close , iom_use, iom_gettime, iom_put 
     25   USE iom        , ONLY : lk_iomput ,jpdom_data,jpdom_autoglo 
     26 
     27   USE par_trc    , ONLY : jptra 
     28   USE par_cfc    , ONLY : lk_cfc   , jp_cfc0 , jp_cfc1 
     29   USE par_c14b   , ONLY : lk_c14b  , jp_c14b0, jp_c14b1 
     30   USE par_pisces , ONLY : lk_pisces, jp_pcs0 , jp_pcs1 
     31   USE par_my_trc , ONLY : lk_my_trc, jp_myt0 , jp_myt1 
     32 
     33   USE trc_oce    , ONLY : lk_degrad, lk_offline, facvol, r_si2, trc_oce_ext_lev 
     34   USE trc_oce    , ONLY : nn_dttrc 
     35   USE trc_oce    , ONLY : etot3 
     36   USE trc        , ONLY : nittrc000 
     37   USE trc        , ONLY : trb,trn,tra 
     38   USE trc        , ONLY : trc2d,trc3d 
     39   USE trc        , ONLY : ctrcnm 
     40   USE trc        , ONLY : numrtr ,numrtw 
     41   USE trc        , ONLY : ln_diatrc,ln_rsttr,ln_top_euler,lrst_trc,ln_trcdmp,ln_trcdmp_clo 
     42   USE trc        , ONLY : gtru, gtrv,gtrui,gtrvi 
     43   USE trc        , ONLY : rdttrc 
     44   USE trc        , ONLY : areatot 
     45   USE trc        , ONLY : cvol 
     46   USE trc        , ONLY : l_trcdm2dc 
     47   USE trc        , ONLY : nn_ice_tr 
     48   USE trc        , ONLY : cn_trc_o 
     49   USE trc        , ONLY : trc_ice_ratio 
     50   USE trc        , ONLY : nn_ice_tr 
     51   USE trc        , ONLY : trc_ice_prescr 
     52   USE trc        , ONLY : qsr_mean ! in case of coarsening no no need to coarsene it because qsr_mean is already in crs space 
    1053 
    1154#if defined key_crs 
     
    123166   USE crs , ONLY :   gdept_crs  =>  gdept_n_crs       !: depth of t-points (m) 
    124167   USE crs , ONLY :   gdept_n    =>  gdept_n_crs       !: depth of t-points (m) 
     168   USE crs , ONLY :   gdepw_n    =>  gdepw_n_crs       !: depth of t-points (m) 
    125169   USE crs , ONLY :   e3t_max_crs => e3t_max_n_crs 
    126170   USE crs , ONLY :   e3u_max_crs => e3u_max_n_crs 
     
    149193   USE crs , ONLY :   gdepw_crs  =>  gdepw_0_crs       !: depth of t-points (m) 
    150194   USE crs , ONLY :   gdept_n    =>  gdept_0_crs       !: depth of t-points (m) 
     195   USE crs , ONLY :   gdepw_n    =>  gdepw_0_crs       !: depth of t-points (m) 
    151196   USE crs , ONLY :   e3t_max_crs => e3t_max_0_crs 
    152197   USE crs , ONLY :   e3u_max_crs => e3u_max_0_crs 
     
    203248   USE crs , ONLY :   fmmflx     =>    fmmflx_crs     !: freshwater budget: volume flux               [Kg/m2/s] 
    204249   USE crs , ONLY :   rnf        =>    rnf_crs        !: river runoff   [Kg/m2/s] 
     250   USE crs , ONLY :   h_rnf      =>    h_rnf_crs      !: river runoff   [Kg/m2/s] 
     251   USE crs , ONLY :   nk_rnf     =>    nk_rnf_crs     !: depth of runoff in model level 
    205252   USE crs , ONLY :   fr_i       =>    fr_i_crs       !: ice fraction (between 0 to 1) 
    206253   USE trcnam_trp , ONLY :  aht0     =>   rn_ahtrc_0        !: horizontal eddy diffusivity for tracers (m2/s) 
     
    218265#endif 
    219266 
    220    USE trc_oce, ONLY : lk_offline 
    221267   USE trc_oce, ONLY : nn_dttrc 
    222268 
     
    302348   USE dom_oce , ONLY :   e1v        =>   e1v        !: horizontal scale factors at v-point (m) 
    303349   USE dom_oce , ONLY :   e2v        =>   e2v        !: horizontal scale factors at v-point (m)   
    304    USE dom_oce , ONLY :   e3t        =>  e3t_0         !: vertical scale factors at t- 
    305    USE dom_oce , ONLY :   e3t_0      =>  e3t_0         !: vertical scale factors at t- 
    306350#if defined key_vvl  
    307351   USE dom_oce , ONLY :     e3t_b    =>  e3t_b 
     
    311355   USE dom_oce , ONLY :     e3v_n    =>  e3v_n 
    312356   USE dom_oce , ONLY :   e3u        =>  e3u_n         !: vertical scale factors at u- 
    313    USE dom_oce , ONLY :   e3u_0      =>  e3u_0         !: vertical scale factors at u- 
    314357   USE dom_oce , ONLY :   e3v        =>  e3v_n         !: vertical scale factors v- 
    315    USE dom_oce , ONLY :   e3v_0      =>  e3v_0         !: vertical scale factors v- 
    316358   USE dom_oce , ONLY :   e3w_n      =>  e3w_n         !: w-points (m) 
    317359   USE dom_oce , ONLY :   e3w        =>  e3w_n         !: w-points (m) 
    318    USE dom_oce , ONLY :   e3w_0      =>  e3w_0         !: w-points (m) 
    319360   USE dom_oce , ONLY :   e3f        =>  e3f_n         !: f-points (m) 
    320361   USE dom_oce , ONLY :   gdept_n    =>  gdept_n         !: f-points (m) 
     362   USE dom_oce , ONLY :   gdepw_n    =>  gdepw_n         !: f-points (m) 
    321363#else 
    322364   USE dom_oce , ONLY :   fse3t_n    =>  e3t_0 
     
    328370   USE dom_oce , ONLY :   fse3t_a    =>  e3t_0 
    329371   USE dom_oce , ONLY :     e3t_a    =>  e3t_0 
     372   USE dom_oce , ONLY :   e3t        =>  e3t_0         !: vertical scale factors at t- 
    330373   USE dom_oce , ONLY :   e3u        =>  e3u_0         !: vertical scale factors at u- 
    331    USE dom_oce , ONLY :   e3u_0      =>  e3u_0         !: vertical scale factors at u- 
    332374   USE dom_oce , ONLY :   e3v        =>  e3v_0         !: vertical scale factors v- 
    333    USE dom_oce , ONLY :   e3v_0      =>  e3v_0         !: vertical scale factors v- 
    334375   USE dom_oce , ONLY :   e3w        =>  e3w_0         !: w-points (m) 
    335    USE dom_oce , ONLY :   e3w_0      =>  e3w_0         !: w-points (m) 
    336376   USE dom_oce , ONLY :   e3f        =>  e3f_0         !: f-points (m) 
    337377   USE dom_oce , ONLY :   gdept_n    =>  gdept_0         !: f-points (m) 
    338    USE dom_oce , ONLY :  fsdept_n    =>  gdept_0         !: f-points (m) 
     378   USE dom_oce , ONLY :   gdepw_n    =>  gdepw_0         !: f-points (m) 
    339379#endif 
    340380   USE dom_oce , ONLY :   ff         =>  ff         !: f-points (m) 
     381   USE dom_oce , ONLY :   e3t_0      =>  e3t_0         !: vertical scale factors at t- 
     382   USE dom_oce , ONLY :   e3u_0      =>  e3u_0         !: vertical scale factors at u- 
     383   USE dom_oce , ONLY :   e3v_0      =>  e3v_0         !: vertical scale factors v- 
     384   USE dom_oce , ONLY :   e3w_0      =>  e3w_0         !: w-points (m) 
    341385   USE dom_oce , ONLY :   gdept_0    =>  gdept_0         !: f-points (m) 
    342386   USE dom_oce , ONLY :   gdept_1d   => gdept_1d          !: f-points (m) 
     
    414458   USE sbc_oce , ONLY :   ln_dm2dc   =>    ln_dm2dc   !: Diurnal Cycle  
    415459   USE sbc_oce , ONLY :   fr_i       =>    fr_i       !: ice fraction (between 0 to 1) 
    416    USE traqsr  , ONLY :   rn_abs     =>    rn_abs     !: fraction absorbed in the very near surface 
    417    USE traqsr  , ONLY :   rn_si0     =>    rn_si0     !: very near surface depth of extinction 
    418    USE traqsr  , ONLY :   ln_qsr_bio =>    ln_qsr_bio !: flag to use or not the biological fluxes for light 
    419460   USE sbcrnf  , ONLY :   rnfmsk     =>    rnfmsk     !: mixed adv scheme in runoffs vicinity (hori.)  
    420461   USE sbcrnf  , ONLY :   rnfmsk_z   =>    rnfmsk_z   !: mixed adv scheme in runoffs vicinity (vert.) 
     
    423464   USE trc , ONLY :  trc_i => trc_i 
    424465   USE trc , ONLY :  trc_o => trc_o 
    425  
    426    USE trc_oce 
    427466 
    428467   !* lateral diffusivity (tracers) * 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/trcdta.F90

    r7332 r7398  
    252252         IF( PRESENT(ptrc) )  ptrc(:,:,:) = ztrcdta(:,:,:) 
    253253         ! 
     254#if ! defined key_crs 
    254255         IF( lwp .AND. kt == nit000 ) THEN 
    255256               clndta = TRIM( sf_dta(1)%clvar )  
     
    264265               WRITE(numout,*) 
    265266         ENDIF 
     267#endif 
    266268         ! 
    267269         CALL wrk_dealloc( jpi, jpj, jpk, ztrcdta ) 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/trcini.F90

    r7256 r7398  
    1717   !!---------------------------------------------------------------------- 
    1818   USE oce_trc         ! shared variables between ocean and passive tracers 
    19    USE trc             ! passive tracers common variables 
    20    USE trcrst          ! passive tracers restart 
     19   USE trc   ,ONLY: ln_rsttr 
     20   USE trcrst,ONLY: trc_rst_read,trc_rst_cal          ! passive tracers restart 
    2121   USE trcnam          ! Namelist read 
    2222   USE trcini_cfc      ! CFC      initialisation 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/trcstp.F90

    r7332 r7398  
    1111   !!---------------------------------------------------------------------- 
    1212   USE oce_trc          ! ocean dynamics and active tracers variables 
    13    USE trc 
     13   USE trc, ONLY: cvol,numont,numstr 
    1414   USE trctrp           ! passive tracers transport 
    1515   USE trcsms           ! passive tracers sources and sinks 
     
    2222   USE iom, ONLY : lk_iomput , iom_close, iom_varid, jpdom_autoglo, iom_get, iom_rstput 
    2323   USE in_out_manager 
    24    USE trcsub 
     24   USE trcsub, ONLY: trc_sub_stp,trc_sub_reset 
    2525   USE dom_oce, ONLY : nday, nmonth, nyear, nsec1jan000, nsec_year 
    26    !USE sbc_oce 
    2726 
    2827   IMPLICIT NONE 
  • branches/2015/dev_r5003_MERCATOR6_CRS/NEMOGCM/NEMO/TOP_SRC/trcsub.F90

    r7332 r7398  
    1616   USE iom_def, ONLY : jprstlib 
    1717   USE lbclnk 
    18    !cbr USE trabbl 
    19    !cbr USE zdf_oce 
    20    !cbr USE domvvl 
    2118   USE divcur, ONLY : div_cur        ! hor. divergence and curl      (div & cur routines) 
    22    USE sbcrnf, ONLY: h_rnf, nk_rnf   ! River runoff  
    2319   USE bdy_oce 
    2420#if defined key_agrif 
Note: See TracChangeset for help on using the changeset viewer.