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 775 for branches/dev_001_GM/NEMO/TOP_SRC/PISCES_SMS/p4zprg.F90 – NEMO

Ignore:
Timestamp:
2007-12-19T14:45:15+01:00 (16 years ago)
Author:
gm
Message:

dev_001_GM - PISCES in F90 : encapsulation of all p4z...F files in module F90 + doctor norme for local variables - compilation OK

File:
1 moved

Legend:

Unmodified
Added
Removed
  • branches/dev_001_GM/NEMO/TOP_SRC/PISCES_SMS/p4zprg.F90

    r774 r775  
     1MODULE p4zprg 
     2   !!====================================================================== 
     3   !!                         ***  MODULE p4zprg  *** 
     4   !! TOP :   PISCES Source Minus Sink manager 
     5   !!====================================================================== 
     6   !! History :   1.0  !  2004-03 (O. Aumont) Original code 
     7   !!             2.0  !  2007-12  (C. Ethe, G. Madec)  F90 
     8   !!---------------------------------------------------------------------- 
     9#if defined key_pisces 
     10   !!---------------------------------------------------------------------- 
     11   !!   'key_pisces'                                       PISCES bio-model 
     12   !!---------------------------------------------------------------------- 
     13   !!   p4z_prg        :  Time loop of passive tracers sms 
     14   !!---------------------------------------------------------------------- 
     15   USE oce_trc         ! 
     16   USE trp_trc 
     17   USE sms 
     18   USE lbclnk 
     19   USE lib_mpp 
     20    
     21   USE p4zint          !  
     22   USE p4zche          !  
     23   USE p4zbio          !  
     24   USE p4zsed          !  
     25   USE p4zlys          !  
     26   USE p4zflx          !  
     27    
     28   IMPLICIT NONE 
     29   PRIVATE 
    130 
    2 CCC $Header$  
    3 CCC  TOP 1.0 , LOCEAN-IPSL (2005)  
    4 C This software is governed by CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
    5 C --------------------------------------------------------------------------- 
    6 CDIR$ LIST 
    7        SUBROUTINE p4zprg(kt) 
    8 CCC--------------------------------------------------------------------- 
    9 CCC 
    10 CCC           ROUTINE p4zprg : PISCES MODEL 
    11 CCC           ***************************** 
    12 CCC 
    13 CCC  PURPOSE : 
    14 CCC  --------- 
    15 CCC     Call Biological sources and sinks subroutines 
    16 CCC 
    17 CC   INPUT : 
    18 CC   ----- 
    19 CC      argument 
    20 CC              ktask           : task identificator 
    21 CC              kt              : time step 
    22 CC      common 
    23 CC              all the common defined in opa 
    24 CC 
    25 CC 
    26 CC   OUTPUT :                   : no 
    27 CC   ------ 
    28 CC 
    29 CC   WORKSPACE : 
    30 CC   --------- 
    31 CC 
    32 CC   EXTERNAL : 
    33 CC   -------- 
    34 CC      p4zche, p4zint, p4zlys, p4zbio, p4zsed, p4zflx 
    35 CC 
    36 CC   MODIFICATIONS: 
    37 CC   -------------- 
    38 CC      original  : O. AUMONT (2004) 
    39 CC---------------------------------------------------------------------- 
    40 CC parameters and commons 
    41 CC ====================== 
    42 CDIR$ NOLIST 
    43       USE trp_trc 
    44       USE sms 
    45 CC 
    46       USE oce_trc 
    47       USE lbclnk 
    48       USE lib_mpp 
    49 CC 
    50       IMPLICIT NONE 
    51 CDIR$ LIST 
    52 CC---------------------------------------------------------------------- 
    53 CC local declarations 
    54 CC ================== 
     31   PUBLIC   p4z_prg    ! called in trcsms.F90 
    5532 
    56       INTEGER kt 
    57 #if defined key_top && defined key_pisces 
    58       INTEGER jnt, jn 
     33   !!---------------------------------------------------------------------- 
     34   !! NEMO/TOP 2.0 , LOCEAN-IPSL (2007)  
     35   !! $Header:$  
     36   !! Software governed by the CeCILL licence (modipsl/doc/NEMO_CeCILL.txt) 
     37   !!---------------------------------------------------------------------- 
    5938 
    60 C 
    61 C this part is without macrotasking coding 
    62 C 
    63 C Call an intermediate routine that in turns, calls chemistry 
    64 C and another routine on a daily basis 
    65 C ----------------------------------------------------------- 
    66 C 
    67       CALL p4zslow(kt) 
     39CONTAINS 
    6840 
    69 C...................................................................... 
    70 C 
    71 C Compute soft tissue production (POC) 
    72 C ------------------------------------ 
    73  
    74        do jnt=1,nrdttrc 
    75 C 
    76          CALL p4zbio 
    77  
    78 C 
    79 C...................................................................... 
    80 C 
    81 C Compute soft tissue remineralisation 
    82 C ------------------------------------ 
    83 C 
    84          CALL p4zsed 
    85  
    86 C 
    87           trb=trn 
    88         END DO 
    89 C 
    90 C...................................................................... 
    91 C 
    92 C Compute CaCO3 saturation 
    93 C ------------------------ 
    94 C 
    95       CALL p4zlys 
    96  
    97 C 
    98 C...................................................................... 
    99 C 
    100 C Compute surface fluxes 
    101 C ---------------------- 
    102 C 
    103       CALL p4zflx 
     41   SUBROUTINE p4z_prg( kt ) 
     42      !!--------------------------------------------------------------------- 
     43      !!                     ***  ROUTINE p4z_prg  *** 
     44      !! 
     45      !! ** Purpose :   Managment of the call to Biological sources and sinks  
     46      !!              routines of PISCES bio-model 
     47      !! 
     48      !! ** Method  : - at each new day ... 
     49      !!              - several calls of bio and sed ??? 
     50      !!              - ... 
     51      !!--------------------------------------------------------------------- 
     52      INTEGER, INTENT( in ) ::   kt      ! ocean time-step index       
     53      !! 
     54      INTEGER ::   jnt, jn 
     55      INTEGER ::   iyy, imm, idd 
     56      !!--------------------------------------------------------------------- 
    10457 
    10558 
    106       DO jn=1 , jptra 
    107         CALL lbc_lnk(trn(:,:,:,jn), 'T', 1. ) 
    108         CALL lbc_lnk(trb(:,:,:,jn), 'T', 1. ) 
    109         CALL lbc_lnk(tra(:,:,:,jn), 'T', 1. ) 
     59      iyy = ndastp/10000 
     60      imm = (ndastp - iyy*10000)/100 
     61      idd = (ndastp - iyy*10000 - imm*100) 
     62 
     63      IF( ndayflxtr /= idd) THEN      ! New days 
     64         ! 
     65         ndayflxtr = idd 
     66 
     67         CALL p4z_che          ! computation of chemical constants 
     68 
     69         CALL p4z_int( kt )    ! computation of various rates for biogeochemistry 
     70         ! 
     71      ENDIF 
     72 
     73 
     74      DO jnt = 1, nrdttrc             ! ??? 
     75         ! 
     76         CALL p4z_bio          ! Compute soft tissue production (POC) 
     77 
     78         CALL p4z_sed          ! compute soft tissue remineralisation 
     79         ! 
     80         trb(:,:,:,:) = trn(:,:,:,:) 
     81         ! 
    11082      END DO 
    11183 
    112 C 
    113 C...................................................................... 
    114 C 
    115 #endif 
    116 C 
    117       RETURN 
    118       END 
     84      CALL p4z_lys             ! Compute CaCO3 saturation 
     85 
     86      CALL p4z_flx             ! Compute surface fluxes 
     87 
     88      DO jn = 1, jptra 
     89        CALL lbc_lnk( trn(:,:,:,jn), 'T', 1. ) 
     90        CALL lbc_lnk( trb(:,:,:,jn), 'T', 1. ) 
     91        CALL lbc_lnk( tra(:,:,:,jn), 'T', 1. ) 
     92      END DO 
     93      ! 
     94   END SUBROUTINE p4z_prg 
     95 
     96#else 
     97   !!====================================================================== 
     98   !!  Dummy module :                                   No PISCES bio-model 
     99   !!====================================================================== 
     100CONTAINS 
     101   SUBROUTINE p4z_prg( kt )                   ! Empty routine 
     102      INTEGER, INTENT( in ) ::   kt 
     103      WRITE(*,*) 'p4z_prg: You should not have seen this print! error?', kt 
     104   END SUBROUTINE p4z_prg 
     105#endif  
     106 
     107   !!====================================================================== 
     108END MODULE  p4zprg 
Note: See TracChangeset for help on using the changeset viewer.