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 15 for trunk/NEMO/OPA_SRC – NEMO

Changeset 15 for trunk/NEMO/OPA_SRC


Ignore:
Timestamp:
2004-02-17T08:25:44+01:00 (20 years ago)
Author:
opalod
Message:

CT : UPDATE001 : First major NEMO update

Location:
trunk/NEMO/OPA_SRC
Files:
27 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/OPA_SRC/cla.F90

    r3 r15  
    164164         END DO 
    165165      END DO 
    166  
    167       ! mpp 
    168 # if defined key_mpp 
    169       CALL mpp_sum( zempred ) 
    170 # endif 
     166      IF( lk_mpp )   CALL mpp_sum( zempred )      ! sum with other processors value 
    171167 
    172168      ! convert in m3 
     
    370366         END DO 
    371367      END DO 
    372  
    373       ! mpp 
    374 # if defined key_mpp 
    375       CALL mpp_sum( zempmed ) 
    376 # endif 
     368      IF( lk_mpp )   CALL mpp_sum( zempmed )      ! sum with other processors value 
     369 
    377370 
    378371      ! minus 2 points in Red Sea and 3 in Atlantic ocean 
  • trunk/NEMO/OPA_SRC/cla_div.F90

    r3 r15  
    126126         END DO 
    127127      END DO 
    128  
    129       ! mpp 
    130 # if defined key_mpp 
    131       CALL mpp_sum( zempred ) 
    132 # endif 
     128      IF( lk_mpp )   CALL mpp_sum( zempred )      ! sum with other processors value 
     129 
    133130 
    134131      ! convert in m3 
     
    239236         END DO 
    240237      END DO 
    241  
    242       ! mpp 
    243 # if defined key_mpp 
    244       CALL mpp_sum( zempmed ) 
    245 # endif 
     238      IF( lk_mpp )   CALL mpp_sum( zempmed )      ! sum with other processors value 
    246239 
    247240      ! minus 2 points in Red Sea and 3 in Atlantic  
     
    536529#else 
    537530   !!---------------------------------------------------------------------- 
    538    !!   Default key                                            Empty module 
     531   !!   Default key                                            Dummy module 
    539532   !!---------------------------------------------------------------------- 
    540533CONTAINS 
    541534   SUBROUTINE div_cla( kt ) 
    542       WRITE(*,*) kt                         ! suppress compilation warning 
     535      WRITE(*,*) 'div_cla: You should have not see this print! error?', kt 
    543536   END SUBROUTINE div_cla 
    544537#endif 
  • trunk/NEMO/OPA_SRC/cla_dynspg.F90

    r3 r15  
    11MODULE cla_dynspg 
    2    !!---------------------------------------------------------------------- 
    3    !!                 ***  dynspg_freesurf_cstvol.h90  *** 
    4    !!---------------------------------------------------------------------- 
     2   !!====================================================================== 
     3   !!                       ***  cla_dynspg  *** 
     4   !!====================================================================== 
    55   !!   dyn_spg      : update the momentum trend with the surface pressure 
    66   !!                  gradient in the free surface constant volume case 
     
    5959      INTEGER, INTENT( in ) ::   kt           ! ocean time-step 
    6060      !! * Local declarations 
    61       INTEGER ::   ji, jj, jk                 ! dummy loop indices 
     61      INTEGER  ::   ji, jj, jk                ! dummy loop indices 
     62      INTEGER  ::   ii0, ii1, ij0, ij1        ! temporary integer 
    6263      REAL(wp) ::    &     
    6364         zempmed, zempred,   &                ! EMP on Med Sea ans Red Sea 
     
    8384      zempmed = 0.e0 
    8485      zwei = 0.e0 
    85       DO jj = mj0(96), mj1(110) 
    86          DO ji = mi0(141),mi1(181) 
     86      ij0 =  96   ;   ij1 = 110 
     87      ii0 = 141   ;   ii1 = 181 
     88      DO jj = mj0(ij0), mj1(ij1) 
     89         DO ji = mi0(ii0),mi1(ii1) 
    8790            zwei    = tmask(ji,jj,1) * e1t(ji,jj) * e2t(ji,jj) 
    8891            zempmed = zempmed + emp(ji,jj) * zwei 
    8992         END DO 
    9093      END DO 
    91  
    92       ! mpp 
    93 # if defined key_mpp 
    94       CALL mpp_sum( zempmed ) 
    95 # endif 
     94      IF( lk_mpp )   CALL mpp_sum( zempmed )      ! sum with other processors value 
    9695 
    9796      ! minus 2 points in Red Sea and 3 in Atlantic  
    98       DO jj = mj0(96), mj1(96) 
    99          DO ji = mi0(148),mi1(148) 
     97      ij0 =  96   ;   ij1 =  96 
     98      ii0 = 148   ;   ii1 = 148 
     99      DO jj = mj0(ij0), mj1(ij1) 
     100         DO ji = mi0(ii0),mi1(ii1) 
    100101            zempmed = zempmed - emp(ji  ,jj) * tmask(ji  ,jj,1) * e1t(ji  ,jj) * e2t(ji  ,jj)   & 
    101102               &              - emp(ji+1,jj) * tmask(ji+1,jj,1) * e1t(ji+1,jj) * e2t(ji+1,jj)    
     
    108109      zempred = 0.e0 
    109110      zwei = 0.e0 
    110       DO jj = mj0(87), mj1(96) 
    111          DO ji = mi0(148), mi1(160)  
     111      ij0 =  87   ;   ij1 =  96 
     112      ii0 = 148   ;   ii1 = 160 
     113      DO jj = mj0(ij0), mj1(ij1) 
     114         DO ji = mi0(ii0),mi1(ii1) 
    112115            zwei      = tmask(ji,jj,1) * e1t(ji,jj) * e2t(ji,jj) 
    113116            zempred   = zempred + emp(ji,jj) * zwei 
    114117         END DO 
    115118      END DO 
    116  
    117       ! mpp 
    118 # if defined key_mpp 
    119       CALL mpp_sum( zempred ) 
    120 # endif 
     119      IF( lk_mpp )   CALL mpp_sum( zempred )      ! sum with other processors value 
    121120 
    122121      ! we convert in m3 
     
    143142      ! Bab el Mandeb 
    144143      ! ------------- 
    145       DO jj = mj0(88), mj1(88)  
    146          DO ji = mi0(160), mi1(160)  
     144      ! 160,88 north point Bab el Mandeb 
     145      ij0 =  88   ;   ij1 =  88 
     146      ii0 = 160   ;   ii1 = 160 
     147      DO jj = mj0(ij0), mj1(ij1) 
     148         DO ji = mi0(ii0),mi1(ii1) 
    147149            ua(ji,jj  ,: ) = 0.e0  !  North East Bab el Mandeb  
    148             ua(ji,jj-1,: ) = 0.e0  !  South East Bab el Mandeb 
    149          END DO 
    150       END DO 
    151   
    152       ! 160,87 north point Bab el Mandeb 
    153       ! surface 
     150         END DO 
     151      END DO 
     152      !                              ! surface 
    154153      DO jk = 1,  8                                       
    155          DO jj = mj0(88), mj1(88)  
    156             DO ji = mi0(160), mi1(160)  
     154         DO jj = mj0(ij0), mj1(ij1) 
     155            DO ji = mi0(ii0),mi1(ii1) 
    157156               ua(ji, jj,jk) = -( ( zisw_rs + zempred ) / 8. ) / ( e2u(ji, jj) * fse3t(ji, jj,jk) )      
    158157            END DO 
    159158         END DO 
    160159      END DO 
    161  
    162       ! deeper 
    163       DO jj = mj0(88), mj1(88)  
    164          DO ji = mi0(160), mi1(160)  
     160      !                              ! deeper 
     161      DO jj = mj0(ij0), mj1(ij1) 
     162         DO ji = mi0(ii0),mi1(ii1) 
    165163            ua(ji, jj,21) = - zbrw_rs / ( e2u(ji, jj) * fse3t(ji, jj,21) ) 
    166164         END DO 
     
    168166 
    169167      ! 160,87 south point Bab el Mandeb 
    170       DO jj = mj0(87), mj1(87)  
    171          DO ji = mi0(160), mi1(160)  
     168      ij0 =  87   ;   ij1 =  87 
     169      ii0 = 160   ;   ii1 = 160 
     170      DO jj = mj0(ij0), mj1(ij1) 
     171         DO ji = mi0(ii0),mi1(ii1) 
     172            ua(ji,jj  ,: ) = 0.e0  !  South East Bab el Mandeb  
     173         END DO 
     174      END DO 
     175      DO jj = mj0(ij0), mj1(ij1) 
     176         DO ji = mi0(ii0),mi1(ii1) 
    172177            ua(ji, jj,21) =  ( zisw_rs + zbrw_rs ) / ( e2u(ji,jj )*fse3t(ji, jj,21) )       
    173178         END DO 
     
    178183 
    179184      ! initialisation of velocity at concerned points  
    180       DO jj = mj0(101), mj1(101)  
    181          DO ji = mi0(139), mi1(139)  
     185      ! 139, 101 south point in Gibraltar  
     186      ij0 = 101   ;   ij1 = 101 
     187      ii0 = 139   ;   ii1 = 139 
     188      DO jj = mj0(ij0), mj1(ij1) 
     189         DO ji = mi0(ii0),mi1(ii1) 
    182190            ua(ji,jj  ,: ) = 0.e0  !  South West Gibraltar 
    183191            ua(ji,jj+1,: ) = 0.e0  !  North West Gibraltar 
    184192         END DO 
    185193      END DO 
    186  
    187       ! 139, 101 south point in Gibraltar  
    188       ! surface 
     194      !                            ! surface 
    189195      DO jk = 1, 14                       
    190          DO jj = mj0(101), mj1(101)  
    191             DO ji = mi0(139), mi1(139)  
     196         DO jj = mj0(ij0), mj1(ij1) 
     197            DO ji = mi0(ii0),mi1(ii1) 
    192198               ua(ji,jj,jk) =  ( ( zisw_ms + zempmed ) / 14. ) / ( e2u(ji,jj) * fse3t(ji,jj,jk) )  
    193199            END DO 
    194200         END DO 
    195201      END DO 
    196  
    197       ! middle circulation 
     202      !                            ! middle circulation 
    198203      DO jk = 15, 20                       
    199          DO jj = mj0(101), mj1(101)  
    200             DO ji = mi0(139), mi1(139)  
     204         DO jj = mj0(ij0), mj1(ij1) 
     205            DO ji = mi0(ii0),mi1(ii1) 
    201206               ua(ji,jj,jk) =  ( zmrw_ms / 6. ) / ( e2u(ji,jj) * fse3t(ji,jj,jk) )  
    202207            END DO 
    203208         END DO 
    204209      END DO 
    205  
    206       ! deeper  
    207       DO jj = mj0(101), mj1(101)  
    208          DO ji = mi0(139), mi1(139)  
     210      !                            ! deeper  
     211      DO jj = mj0(ij0), mj1(ij1) 
     212         DO ji = mi0(ii0),mi1(ii1) 
    209213            ua(ji,jj,21) =             zurw_ms   / ( e2u(ji,jj) * fse3t(ji,jj,21) ) 
    210214            ua(ji,jj,22) = ( zbrw_ms - zurw_ms ) / ( e2u(ji,jj) * fse3t(ji,jj,22) ) 
     
    213217 
    214218      ! 139,102 north point in Gibraltar 
     219      ij0 = 102   ;   ij1 = 102 
     220      ii0 = 139   ;   ii1 = 139 
     221      DO jj = mj0(ij0), mj1(ij1) 
     222         DO ji = mi0(ii0),mi1(ii1) 
     223            ua(ji,jj  ,: ) = 0.e0  !  North West Gibraltar 
     224         END DO 
     225      END DO 
    215226      DO jk = 15, 20                       
    216          DO jj = mj0(102), mj1(102)  
    217             DO ji = mi0(139), mi1(139)  
     227         DO jj = mj0(ij0), mj1(ij1) 
     228            DO ji = mi0(ii0),mi1(ii1) 
    218229               ua(ji,jj,jk) = -( zmrw_ms / 6. ) / ( e2u(ji,jj) * fse3t(ji,jj,jk) )  
    219230            END DO 
    220231         END DO 
    221232      END DO 
    222  
    223       ! deeper 
    224       DO jj = mj0(102), mj1(102)  
    225          DO ji = mi0(139), mi1(139)  
     233      !                            ! deeper 
     234      DO jj = mj0(ij0), mj1(ij1) 
     235         DO ji = mi0(ii0),mi1(ii1) 
    226236            ua(ji,jj,22) = -( zisw_ms + zbrw_ms ) / ( e2u(ji,jj) * fse3t(ji,jj,22) ) 
    227237         END DO 
     
    229239 
    230240   END SUBROUTINE dyn_spg_cla 
     241 
     242   !!====================================================================== 
    231243END MODULE cla_dynspg 
  • trunk/NEMO/OPA_SRC/cpl.F90

    r3 r15  
    773773   END SUBROUTINE cpl_init 
    774774   SUBROUTINE cpl_step( kt )       ! Dummy routine 
    775       WRITE(*,*) kt 
     775      WRITE(*,*) 'cpl_step: You should have not see this print! error?', kt 
    776776   END SUBROUTINE cpl_step 
    777777#endif 
  • trunk/NEMO/OPA_SRC/daymod.F90

    r3 r15  
    2020 
    2121   !! * Shared module variables 
    22    INTEGER, PUBLIC ::         & 
    23       nyear   ,               &  ! current year 
    24       nmonth  ,               &  ! current month 
    25       nday    ,               &  ! current day of the month 
    26       nday_year ,             &  ! curent day counted from jan 1st of the current year 
    27       ndastp                     ! time step date in year/month/day aammjj 
    28  
    29     REAL(wp), PUBLIC ::     & 
    30           adatrj ,          &   ! (non integer) number of elapsed days since the begining of the experiment 
    31           adatrj0               !  value of adatrj at nit000-1 (before the present run). 
    32                                 ! it is the accumulated duration of previous runs 
    33                                 ! that may have been run with different time steps. 
    34  
     22   INTEGER , PUBLIC ::   &  !: 
     23      nyear     ,   &  !: current year 
     24      nmonth    ,   &  !: current month 
     25      nday      ,   &  !: current day of the month 
     26      nday_year ,   &  !: curent day counted from jan 1st of the current year 
     27      ndastp           !: time step date in year/month/day aammjj 
     28   REAL(wp), PUBLIC ::   &  !: 
     29       adatrj   ,   &  !: number of elapsed days since the begining of the run 
     30       adatrj0         !: value of adatrj at nit000-1 (before the present run). 
     31       !               !  it is the accumulated duration of previous runs 
     32       !               !  that may have been run with different time steps. 
     33   !!---------------------------------------------------------------------- 
     34   !!  OPA 9, LODYC-IPSL (2004) 
    3535   !!---------------------------------------------------------------------- 
    3636 
    3737CONTAINS 
    3838 
    39    SUBROUTINE day ( kt ) 
     39   SUBROUTINE day( kt ) 
    4040      !!---------------------------------------------------------------------- 
    41       !!                  ***  ROUTINE day  *** 
     41      !!                      ***  ROUTINE day  *** 
    4242      !!  
    4343      !! ** Purpose :   Compute the date with a day iteration IF necessary. 
     
    5050      !!              - nday_year : current day of the year nyear 
    5151      !!              - ndastp    : =nyear*10000+nmonth*100+nday 
    52       !!              - adatrj    : date in days since the beginning 
    53       !!                            of the experiment 
     52      !!              - adatrj    : date in days since the beginning of the run 
    5453      !! 
    5554      !! History : 
     
    6968      REAL(wp) :: zadatrjn, zadatrjb     ! adatrj at timestep kt-1 and kt-2  
    7069      !!---------------------------------------------------------------------- 
    71       !!  OPA 9, LODYC-IPSL (2004) 
    72       !!---------------------------------------------------------------------- 
    7370 
    7471      ! 0.  initialization of adatrj0 and nday, nmonth,nyear, nday_year. 
     
    7673      !----------------------------------------------------------------- 
    7774 
    78       IF ( kt == nit000 ) THEN 
     75      IF( kt == nit000 ) THEN 
    7976 
    80          IF ( .NOT.ln_rstart )   adatrj0 = 0.e0      ! adatrj0 initialized in rst_read when restart  
     77         IF( .NOT.ln_rstart )   adatrj0 = 0.e0      ! adatrj0 initialized in rst_read when restart  
    8178 
    8279         adatrj  = adatrj0 
     
    115112      iday1 = INT( zadatrjn ) 
    116113 
    117       if ( iday1 - iday0 >= 1 .AND. ( kt /= nit000 .OR. nrstdt == 2 ) ) THEN 
     114      IF( iday1 - iday0 >= 1 .AND. ( kt /= nit000 .OR. nrstdt == 2 ) ) THEN 
    118115 
    119116         ! increase calendar 
  • trunk/NEMO/OPA_SRC/eosbn2.F90

    r3 r15  
    3737 
    3838   !! * Share module variables 
    39    INTEGER, PUBLIC ::   & !!! nameos : ocean physical parameters 
    40       neos     ,        &  ! = 0/1/2 type of eq. of state and Brunt-Vaisala frequ. 
    41       neos_init = 0        ! control flag for initialization 
    42  
    43    REAL(wp), PUBLIC ::   & !!! nameos : ocean physical parameters 
    44       ralpha,            &  ! thermal expension coeff. (linear equation of state) 
    45       rbeta                 ! saline  expension coeff. (linear equation of state) 
     39   INTEGER , PUBLIC ::   &  !: nameos : ocean physical parameters 
     40      neos          ,    &  !: = 0/1/2 type of eq. of state and Brunt-Vaisala frequ. 
     41      neos_init = 0         !: control flag for initialization 
     42 
     43   REAL(wp), PUBLIC ::   &  !: nameos : ocean physical parameters 
     44      ralpha        ,    &  !: thermal expension coeff. (linear equation of state) 
     45      rbeta                 !: saline  expension coeff. (linear equation of state) 
    4646    
    4747   !! * Substitutions 
     
    594594      !!         The brunt-vaisala frequency is computed using the polynomial 
    595595      !!      polynomial expression of McDougall (1987): 
    596       !!            N^2 = g * beta * ( alpha/beta*dk[ t ] - dk[ s ] )/e3w 
     596      !!            N^2 = grav * beta * ( alpha/beta*dk[ t ] - dk[ s ] )/e3w 
    597597      !!      If lk_zdfddm=T, the heat/salt buoyancy flux ratio Rrau is 
    598598      !!      computed and used in zdfddm module : 
    599599      !!              Rrau = alpha/beta * ( dk[ t ] / dk[ s ] ) 
    600600      !!       * neos = 1  : linear equation of state (temperature only) 
    601       !!            N^2 = g * ralpha * dk[ t ]/e3w 
     601      !!            N^2 = grav * ralpha * dk[ t ]/e3w 
    602602      !!       * neos = 2  : linear equation of state (temperature & salinity) 
    603       !!            N^2 = g * (ralpha * dk[ t ] - rbeta * dk[ s ] ) / e3w 
     603      !!            N^2 = grav * (ralpha * dk[ t ] - rbeta * dk[ s ] ) / e3w 
    604604      !!      The use of potential density to compute N^2 introduces e r r o r 
    605605      !!      in the sign of N^2 at great depths. We recommand the use of  
     
    631631      REAL(wp) ::   & 
    632632         zgde3w, zt, zs, zh,  &  ! temporary scalars  
    633          zalbet, zbeta, zds      !    "         " 
     633         zalbet, zbeta           !    "         " 
     634#if defined key_zdfddm 
     635      REAL(wp) ::   zds          ! temporary scalars 
     636#endif 
    634637      !!---------------------------------------------------------------------- 
    635638      !!  OPA8.5, LODYC-IPSL (2002) 
     
    653656            DO jj = 1, jpj 
    654657               DO ji = 1, jpi 
    655                   zgde3w = g/fse3w(ji,jj,jk) 
    656                   zt = 0.5*( ptem(ji,jj,jk) + ptem(ji,jj,jk-1) )          ! potential temperature at w-point 
    657                   zs = 0.5*( psal(ji,jj,jk) + psal(ji,jj,jk-1) ) - 35.0   ! salinity anomaly (s-35) at w-point 
    658                   zh = fsdepw(ji,jj,jk)                                   ! depth in meters  at w-point 
     658                  zgde3w = grav / fse3w(ji,jj,jk) 
     659                  zt = 0.5 * ( ptem(ji,jj,jk) + ptem(ji,jj,jk-1) )          ! potential temperature at w-point 
     660                  zs = 0.5 * ( psal(ji,jj,jk) + psal(ji,jj,jk-1) ) - 35.0   ! salinity anomaly (s-35) at w-point 
     661                  zh = fsdepw(ji,jj,jk)                                     ! depth in meters  at w-point 
    659662 
    660663                  zalbet = ( ( ( - 0.255019e-07 * zt + 0.298357e-05 ) * zt   &   ! ratio alpha/beta 
     
    706709            DO jj = 1, jpj 
    707710               DO ji = 1, jpi 
    708                   zgde3w = g/fse3w(ji,jj,jk) * tmask(ji,jj,jk) 
     711                  zgde3w = grav / fse3w(ji,jj,jk) * tmask(ji,jj,jk) 
    709712                  pn2(ji,jj,jk) = zgde3w * ralpha * ( ptem(ji,jj,jk-1) - ptem(ji,jj,jk) ) 
    710713               END DO 
     
    722725            DO jj = 1, jpj 
    723726               DO ji = 1, jpi 
    724                   zgde3w = g/fse3w(ji,jj,jk) * tmask(ji,jj,jk) 
     727                  zgde3w = grav / fse3w(ji,jj,jk) * tmask(ji,jj,jk) 
    725728                  pn2(ji,jj,jk) = zgde3w * (  ralpha * ( ptem(ji,jj,jk-1) - ptem(ji,jj,jk) )   & 
    726729                     &                      - rbeta  * ( psal(ji,jj,jk-1) - psal(ji,jj,jk) )  ) 
  • trunk/NEMO/OPA_SRC/ice_oce.F90

    r3 r15  
    1717   USE blk_oce         ! bulk parameters 
    1818 
    19  
    2019   IMPLICIT NONE 
     20   PRIVATE 
    2121  
    2222   !! Shared module variables 
    23    LOGICAL, PUBLIC, PARAMETER ::   lk_ice_lim = .TRUE.    ! LIM ice model 
     23   LOGICAL, PUBLIC, PARAMETER ::   lk_ice_lim = .TRUE.    !: LIM ice model 
    2424 
    2525   !!---------------------------------------------------------------------- 
     
    2727   !!---------------------------------------------------------------------- 
    2828# if defined key_coupled 
    29    REAL(wp), DIMENSION(jpiglo,jpjglo)    ::   & ! cumulated fields 
    30       fqsr_oce ,     &   ! Net short wave heat flux on free ocean  
    31       fqsr_ice ,     &   ! Net short wave het flux on sea ice  
    32       fqnsr_oce,     &   ! Net longwave heat flux on free ocean 
    33       fqnsr_ice,     &   ! Net longwave heat flux on sea ice 
    34       fdqns_ice,     &   ! Derivative of non solar heat flux on sea ice 
    35       ftprecip ,     &   ! Water flux (liquid precipitation - evaporation)  
    36       fsprecip ,     &   ! Solid (snow) precipitation 
    37       frunoff  ,     &   ! runoff 
    38       fcalving           ! Iceberg calving  
     29   REAL(wp), PUBLIC, DIMENSION(jpiglo,jpjglo) ::   &  !: cumulated fields 
     30      fqsr_oce ,      &   !: Net short wave heat flux on free ocean  
     31      fqsr_ice ,      &   !: Net short wave het flux on sea ice  
     32      fqnsr_oce,      &   !: Net longwave heat flux on free ocean 
     33      fqnsr_ice,      &   !: Net longwave heat flux on sea ice 
     34      fdqns_ice,      &   !: Derivative of non solar heat flux on sea ice 
     35      ftprecip ,      &   !: Water flux (liquid precipitation - evaporation)  
     36      fsprecip ,      &   !: Solid (snow) precipitation 
     37      frunoff  ,      &   !: runoff 
     38      fcalving            !: Iceberg calving  
    3939# endif 
    4040 
    41    REAL(wp), DIMENSION(jpi,jpj)    ::   & ! field exchanges with ice model to ocean 
    42       sst_io  ,      &   ! sea surface temperature 
    43       sss_io  ,      &   ! sea surface salinity 
    44       u_io    ,      &   ! i-horizontal velocity at ice surface 
    45       v_io    ,      &   ! j-horizontal velocity at ice surface 
    46       fsolar  ,      &   ! solar heat flux 
    47       fnsolar ,      &   ! total non-solar heat flux 
    48       fsalt   ,      &   ! salt flux 
    49       fmass   ,      &   ! freshwater flux 
    50       ftaux   ,      &   ! i-horizontal wind stress  
    51       ftauy   ,      &   ! j-horizontal wind stress  
    52       gtaux   ,      &   ! i-horizontal wind stress  
    53       gtauy              ! i-horizontal wind stress  
     41   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   &  !: field exchanges with ice model to ocean 
     42      sst_io, sss_io , &  !: sea surface temperature (C) and salinity (PSU) 
     43      u_io  , v_io   , &  !: velocity at ice surface (m/s) 
     44      fsolar, fnsolar, &  !: solar and non-solar heat fluxes (W/m2) 
     45      fsalt , fmass  , &  !: salt and freshwater fluxes 
     46      ftaux , ftauy  , &  !: wind stresses 
     47      gtaux , gtauy       !: wind stresses 
    5448    
    55    REAL(wp) ::       & 
    56       rdt_ice,       &  ! ice time step 
    57       dtsd2              ! ice time step divide by 2 
     49   REAL(wp), PUBLIC ::   &  !: 
     50      rdt_ice,           &  !: ice time step 
     51      dtsd2                 !: ice time step divide by 2 
    5852 
    5953#else 
     
    6155   !!   Default option                                 NO LIM sea-ice model 
    6256   !!---------------------------------------------------------------------- 
    63    LOGICAL, PUBLIC, PARAMETER ::   lk_ice_lim = .FALSE.        ! No LIM ice model 
     57   LOGICAL, PUBLIC, PARAMETER ::   lk_ice_lim = .FALSE.  !: No LIM ice model 
    6458#endif 
    6559 
    66    INTEGER ::         & !!! namdom : space/time domain (namlist) 
    67       nfice =  5         ! coupling frequency OPA ICELLN  nfice  
     60   INTEGER, PUBLIC ::   &  !: namdom : space/time domain (namlist) 
     61      nfice =  5           !: coupling frequency OPA ICELLN  nfice  
    6862 
    6963   !!---------------------------------------------------------------------- 
  • trunk/NEMO/OPA_SRC/in_out_manager.F90

    r3 r15  
    44   USE par_kind 
    55 
     6   PUBLIC 
     7 
    68   !!---------------------------------------------------------------------- 
    79   !! namelist parameters 
    810   !! ------------------------------------- 
    911   ! namrun:  parameters of the run 
    10    CHARACTER (len=16) ::    & 
    11       cexper = "exp0"          ! experiment name used for output filename 
     12   CHARACTER (len=16) ::    &   !: 
     13      cexper = "exp0"           !: experiment name used for output filename 
    1214    
    13    LOGICAL ::   &              !!! * namelist namrun * 
    14       ln_rstart = .FALSE. ,  &  ! start from (F) rest or (T) a restart file 
    15       ln_ctl    = .FALSE.       ! run control for debugging 
     15   LOGICAL ::   &              !!: * namelist namrun * 
     16      ln_rstart = .FALSE. ,  &  !: start from (F) rest or (T) a restart file 
     17      ln_ctl    = .FALSE.       !: run control for debugging 
    1618    
    17    INTEGER ::                & !!! * namelist namrun * 
    18       no     = 0        ,    &  ! job number 
    19       nrstdt = 0        ,    &  ! control of the time step (0, 1 or 2) 
    20       nit000 = 1        ,    &  ! index of the first time step 
    21       nitend = 10       ,    &  ! index of the last time step 
    22       ndate0 = 961115   ,    &  ! initial calendar date aammjj 
    23       nleapy = 0        ,    &  ! Leap year calendar flag (0/1 or 30) 
    24       ninist = 0                ! initial state output flag (0/1) 
     19   INTEGER ::                & !!: * namelist namrun * 
     20      no     = 0        ,    &  !: job number 
     21      nrstdt = 0        ,    &  !: control of the time step (0, 1 or 2) 
     22      nit000 = 1        ,    &  !: index of the first time step 
     23      nitend = 10       ,    &  !: index of the last time step 
     24      ndate0 = 961115   ,    &  !: initial calendar date aammjj 
     25      nleapy = 0        ,    &  !: Leap year calendar flag (0/1 or 30) 
     26      ninist = 0                !: initial state output flag (0/1) 
    2527   !!---------------------------------------------------------------------- 
    2628   !!                          Run control   
    2729   !!---------------------------------------------------------------------- 
    2830    
    29    INTEGER ::                &  ! 
    30       nstop = 0 ,            &  ! e r r o r  flag (=number of reason for a 
    31       !                         !                  prematurely stop the run) 
    32       nwarn = 0                 ! w a r n i n g  flag (=number of warning 
    33       !                         !                      found during the run) 
     31   INTEGER ::                &  !: 
     32      nstop = 0 ,            &  !: e r r o r  flag (=number of reason for a 
     33      !                         !                   prematurely stop the run) 
     34      nwarn = 0                 !: w a r n i n g  flag (=number of warning 
     35      !                         !                       found during the run) 
    3436 
    3537    
    36    CHARACTER (len=64) ::        & 
    37       cform_err="(/,' ===>>> : E R R O R',     /,'         ===========',/)"    ,   & 
    38       cform_war="(/,' ===>>> : W A R N I N G', /,'         ===============',/)" 
     38   CHARACTER (len=64) ::        &                                                    !: 
     39      cform_err="(/,' ===>>> : E R R O R',     /,'         ===========',/)"    ,   & !: 
     40      cform_war="(/,' ===>>> : W A R N I N G', /,'         ===============',/)"      !: 
    3941   !!---------------------------------------------------------------------- 
    4042   !! output monitoring 
    4143   !! ----------------------------------- 
    4244 
    43    LOGICAL ::   & 
    44       lwp                ,   &  ! boolean : true on the 1st processor only 
    45       l_ctl                     ! = ln_ctl.AND.lwp (print control on the 1st proc) 
     45   LOGICAL ::   &               !: 
     46      lwp                ,   &  !: boolean : true on the 1st processor only 
     47      l_ctl                     !: = ln_ctl.AND.lwp (print control on the 1st proc) 
    4648 
    47    INTEGER ::                & 
    48       nstock = 10 ,          &  ! restart file frequency 
    49       nprint =  0 ,          &  ! level of print (0 no print) 
    50       nwrite = 10               ! restart file frequency 
     49   INTEGER ::                &  !: 
     50      nstock = 10 ,          &  !: restart file frequency 
     51      nprint =  0 ,          &  !: level of print (0 no print) 
     52      nwrite = 10               !: restart file frequency 
    5153   !!---------------------------------------------------------------------- 
    5254   !! logical units 
    5355   !! ------------------------------ 
    54    INTEGER ::                & 
    55       numstp     =  1 ,      &  ! logical unit for time step 
    56       numout     =  2 ,      &  ! logical unit for output print 
    57       numnam     =  3 ,      &  ! logical unit for namelist 
    58       numnam_ice =  4 ,      &  ! logical unit for ice namelist 
    59       nummpp     =  8 ,      &  ! logical unit for mpp test print 
    60       numevo_ice = 17 ,      &  ! logical unit for ice variables (temp. evolution) 
    61       numsol     = 25 ,      &  ! logical unit for solver statistics 
    62       numwri     = 40 ,      &  ! logical unit for output write 
    63       numisp     = 41 ,      &  ! logical unit for island statistics 
    64       numwrs     = 46 ,      &  ! logical unit for output restart 
    65       numtdt     = 62 ,      &  ! logical unit for data temperature 
    66       numsdt     = 63 ,      &  ! logical unit for data salinity 
    67       numwso     = 71 ,      &  ! logical unit for 2d output write 
    68       numwvo     = 72 ,      &  ! logical unit for 3d output write 
    69       numsst     = 65 ,      &  ! logical unit for surface temperature data 
    70       numgap     = 45 ,      &  ! logical unit for differences diagnostic 
    71       numbol     = 67 ,      &  ! logical unit for "bol" diagnostics 
    72       numptr     = 68 ,      &  ! logical unit for Poleward TRansports 
    73       numflo     = 69           ! logical unit for drifting floats 
     56   INTEGER ::                &  !: 
     57      numstp     =  1 ,      &  !: logical unit for time step 
     58      numout     =  2 ,      &  !: logical unit for output print 
     59      numnam     =  3 ,      &  !: logical unit for namelist 
     60      numnam_ice =  4 ,      &  !: logical unit for ice namelist 
     61      nummpp     =  8 ,      &  !: logical unit for mpp test print 
     62      numevo_ice = 17 ,      &  !: logical unit for ice variables (temp. evolution) 
     63      numsol     = 25 ,      &  !: logical unit for solver statistics 
     64      numwri     = 40 ,      &  !: logical unit for output write 
     65      numisp     = 41 ,      &  !: logical unit for island statistics 
     66      numwrs     = 46 ,      &  !: logical unit for output restart 
     67      numtdt     = 62 ,      &  !: logical unit for data temperature 
     68      numsdt     = 63 ,      &  !: logical unit for data salinity 
     69      numwso     = 71 ,      &  !: logical unit for 2d output write 
     70      numwvo     = 72 ,      &  !: logical unit for 3d output write 
     71      numsst     = 65 ,      &  !: logical unit for surface temperature data 
     72      numgap     = 45 ,      &  !: logical unit for differences diagnostic 
     73      numbol     = 67 ,      &  !: logical unit for "bol" diagnostics 
     74      numptr     = 68 ,      &  !: logical unit for Poleward TRansports 
     75      numflo     = 69 ,      &  !: logical unit for drifting floats 
     76      !                         !: * coupled units 
     77      numlhf     = 71 ,      &  !: unit to transfer fluxes 
     78      numlws     = 72 ,      &  !: unit to transfer stress 
     79      numlts     = 73 ,      &  !: unit to transfer sst 
     80      numlic     = 74           !: unit to transfer ice cover 
     81 
    7482 
    7583   !! Contral/debugging 
    7684   !! ----------------- 
    77    REAL(wp) ::               & 
    78       u_ctl, v_ctl,          &  ! sum of ua and va trend 
    79       t_ctl, s_ctl              ! sum of ta and sa trend 
     85   REAL(wp) ::               &  !: 
     86      u_ctl, v_ctl,          &  !: sum of ua and va trend 
     87      t_ctl, s_ctl              !: sum of ta and sa trend 
    8088 
    8189END MODULE in_out_manager 
  • trunk/NEMO/OPA_SRC/istate.F90

    r3 r15  
    7474      rhop (:,:,:) = 0.e0 
    7575      rn2  (:,:,:) = 0.e0  
    76    
    77  
    78  
    79       IF( ln_rstart ) THEN                       ! Restart from a file 
     76 
     77#if defined key_dynspg_fsc 
     78      ! free surface formulation 
     79      sshb(:,:) = 0.e0      ! before sea-surface height 
     80      sshn(:,:) = 0.e0      ! now    sea-surface height 
     81#endif 
     82#if defined key_dynspg_rl 
     83      ! rigid-lid formulation 
     84      bsfb(:,:) = 0.e0      ! before barotropic stream-function 
     85      bsfn(:,:) = 0.e0      ! now    barotropic stream-function 
     86      bsfd(:,:) = 0.e0      ! barotropic stream-function trend 
     87#endif  
     88 
     89 
     90      IF( ln_rstart ) THEN                    ! Restart from a file 
    8091         !                                    ! ------------------- 
    8192         neuler = 1                              ! Set time-step indicator at nit000 (leap-frog) 
     
    148159            DO ji = 1, jpi 
    149160               tn(ji,jj,jk) = (  ( ( 7.5 - 0.*ABS(gphit(ji,jj))/30. )   & 
    150                                   *( 1.-TANH((fsdept(ji,jj,jk)-80.)/30.) )   & 
    151                                + 10.*(5000.-fsdept(ji,jj,jk))/5000.)  ) * tmask(ji,jj,jk) 
     161                  &               *( 1.-TANH((fsdept(ji,jj,jk)-80.)/30.) )   & 
     162                  &            + 10.*(5000.-fsdept(ji,jj,jk))/5000.)  ) * tmask(ji,jj,jk) 
    152163               tb(ji,jj,jk) = tn(ji,jj,jk) 
    153164          END DO 
     
    283294 
    284295            DO jj = 1, jpjglo 
    285                zssh(:,jj) = ( .22 - ( float(jj-3) * (0.44) ) / 99. ) 
     296               zssh(:,jj) = ( .22 - ( FLOAT(jj-3) * (0.44) ) / 99. ) 
    286297            END DO 
    287298            DO jj = 1, nlcj 
     
    403414      ! ------------------------------------ 
    404415 
    405       zalfg = 0.5 * g * rau0 
     416      zalfg = 0.5 * grav * rau0 
    406417      ! Surface value 
    407418      zprn(:,:,1) = zalfg * fse3w(:,:,1) * ( 1 + rhd(:,:,1) ) 
  • trunk/NEMO/OPA_SRC/lbclnk.F90

    r3 r15  
    44   !! Ocean        : lateral boundary conditions 
    55   !!===================================================================== 
    6 #if defined key_mpp 
    7    !!---------------------------------------------------------------------- 
    8    !!   'key_mpp'  :                           distributed memory computing 
     6#if   defined key_mpp_mpi   ||   defined key_mpp_shmem 
     7   !!---------------------------------------------------------------------- 
     8   !!   'key_mpp_mpi'     OR      MPI massively parallel processing library 
     9   !!   'key_mpp_shmem'         SHMEM massively parallel processing library 
     10   !!---------------------------------------------------------------------- 
    911   !!---------------------------------------------------------------------- 
    1012   !!   lbc_lnk      : generic interface for mpp_lnk_3d and mpp_lnk_2d 
  • trunk/NEMO/OPA_SRC/lib_io_fdir.F90

    r3 r15  
    6161         krec            ! record unit for direct access file 
    6262 
    63 #if defined key_mpp 
     63#if defined key_mpp_mpi   ||   defined key_mpp_shmem 
    6464   !! * Local declarations 
    6565      INTEGER ji, jj, jproc   ! dummy loop indices 
     
    139139         krec            ! record unit for direct access file 
    140140 
    141 #if defined key_mpp 
     141#if defined key_mpp_mpi   ||   defined key_mpp_shmem 
    142142      INTEGER ji, jj, jproc 
    143143      INTEGER imess, ic 
     
    221221         krec            ! record unit for direct access file 
    222222 
    223 #if defined key_mpp 
     223#if defined key_mpp_mpi   ||   defined key_mpp_shmem 
    224224      INTEGER ji, jj, jk, jproc 
    225225      INTEGER ikloc, ikpe 
     
    313313         krec            ! record unit for direct access file 
    314314 
    315 #if defined key_mpp 
     315#if defined key_mpp_mpi   ||   defined key_mpp_shmem 
    316316      INTEGER ji, jj, jk, jproc 
    317317      INTEGER ikloc, ikpe 
     
    405405         krec            ! record unit for direct access file 
    406406 
    407 #if defined key_mpp 
     407#if defined key_mpp_mpi   ||   defined key_mpp_shmem 
    408408      INTEGER ji,jj,jproc 
    409409      INTEGER ildi,ilei,ildj,ilej 
     
    488488         krec            ! record unit for direct access file 
    489489 
    490 #if defined key_mpp 
     490#if defined key_mpp_mpi   ||   defined key_mpp_shmem 
    491491      INTEGER ji,jj,jk,jproc 
    492492      INTEGER ikloc,ikpe 
     
    584584         ptab            ! variable array 
    585585 
    586 #if defined key_mpp 
     586#if defined key_mpp_mpi   ||   defined key_mpp_shmem 
    587587   !! * Local declarations 
    588588      INTEGER jk, jproc 
  • trunk/NEMO/OPA_SRC/module_example

    r3 r15  
    2424 
    2525   !! * Share Module variables 
    26    REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   & 
     26   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   &  !: 
    2727      var1    ,   &  !: var1 description (CAUTION always use !: to describe a  
    2828      !              !  PUBLIC variable simplify the search of where it is declared 
     
    103103 
    104104 
    105       IF( kt == nit000  )   CALL zdf_tke_init    ! Initialization (first time-step only) 
     105      IF( kt == nit000  )   CALL exa_mpl_init    ! Initialization (first time-step only) 
    106106 
    107107      ! Local constant initialization 
     
    193193      ENDIF 
    194194 
    195    END SUBROUTINE zdf_tke_init 
     195   END SUBROUTINE exa_mpl_init 
    196196 
    197197#else 
  • trunk/NEMO/OPA_SRC/mppini.F90

    r3 r15  
    3131CONTAINS 
    3232 
    33 #if ! defined key_mpp 
     33#if ! defined key_mpp_mpi   &&   ! defined key_mpp_shmem 
    3434   !!---------------------------------------------------------------------- 
    3535   !!   Default option :                            shared memory computing 
     
    4747      !! History : 
    4848      !!   9.0  !  04-01  (G. Madec, J.M. Molines)  F90 : free form, north fold jpni >1 
    49       !!---------------------------------------------------------------------- 
    50       !!  OPA 9.0, LODYC-IPSL (2004) 
    5149      !!---------------------------------------------------------------------- 
    5250      ! No mpp computation 
     
    8886#else 
    8987   !!---------------------------------------------------------------------- 
    90    !!   'key_mpp' :                            distributed memory computing 
     88   !!   'key_mpp_mpi'          OR         MPI massively parallel processing 
     89   !!   'key_mpp_shmem'                 SHMEM massively parallel processing 
    9190   !!---------------------------------------------------------------------- 
    9291 
     
    140139      !!---------------------------------------------------------------------- 
    141140 
    142 #if defined key_mpp_pvm 
    143       IF(lwp)WRITE(numout,*) 
    144       IF(lwp)WRITE(numout,*) 'mpp_init : Message Passing PVM' 
    145       IF(lwp)WRITE(numout,*) '~~~~~~~~' 
    146 #endif 
    147141#if defined key_mpp_shmem 
    148142      IF(lwp)WRITE(numout,*) 
     
    156150      IF(lwp)WRITE(numout,*) 
    157151      IF(lwp)WRITE(numout,*) 'mpp_init : Message Passing MPI' 
    158       IF(lwp)WRITE(numout,*) '~~~~~~~~' 
    159 #endif 
    160 #if ! defined key_mpp_pvm &&  ! defined key_mpp_mpi && ! defined key_mpp_shmem 
    161       IF(lwp)WRITE(numout,*) 
    162       IF(lwp)WRITE(numout,*) 'mpp_init : Message Passing PVM onto T3E' 
    163152      IF(lwp)WRITE(numout,*) '~~~~~~~~' 
    164153#endif 
  • trunk/NEMO/OPA_SRC/mppini_2.h90

    r3 r15  
    7070      !!---------------------------------------------------------------------- 
    7171 
    72 #if defined key_mpp_pvm 
    73       IF(lwp)WRITE(numout,*) 
    74       IF(lwp)WRITE(numout,*) 'mpp_init : Message Passing PVM' 
    75       IF(lwp)WRITE(numout,*) '~~~~~~~~' 
    76 #endif 
    7772#if defined key_mpp_shmem 
    7873      IF(lwp)WRITE(numout,*) 
     
    8984      IF(lwp)WRITE(numout,*) '~~~~~~~~' 
    9085      IF(lwp)WRITE(numout,*) ' ' 
    91 #endif 
    92 #if ! defined key_mpp_pvm &&  ! defined key_mpp_mpi && ! defined key_mpp_shmem 
    93       IF(lwp)WRITE(numout,*) 
    94       IF(lwp)WRITE(numout,*) 'mpp_init : Message Passing PVM onto T3E' 
    95       IF(lwp)WRITE(numout,*) '~~~~~~~~' 
    9686#endif 
    9787 
  • trunk/NEMO/OPA_SRC/oce.F90

    r3 r15  
    11MODULE oce 
    22   !!====================================================================== 
    3    !!             ***  MODULE  oce  *** 
     3   !!                      ***  MODULE  oce  *** 
    44   !! Ocean        :  dynamics and active tracers defined in memory  
    55   !!====================================================================== 
     
    1313 
    1414   IMPLICIT NONE 
     15   PRIVATE 
    1516 
    1617   !! Physics and algorithm flags 
    1718   !! --------------------------- 
    18 #if defined key_vectopt_memory 
    19    LOGICAL ::   l_vopt   = .TRUE.   !: memory vector optimization flag 
    20 #else 
    21    LOGICAL ::   l_vopt   = .FALSE.  !: memory vector optimization flag 
    22 #endif 
    23  
    24    LOGICAL ::   ln_dynhpg_imp   = .FALSE.  ! semi-implicite hpg flag 
     19   LOGICAL, PUBLIC ::   ln_dynhpg_imp   = .FALSE.  !: semi-implicite hpg flag 
    2520 
    2621   !! dynamics and tracer fields 
    2722   !! -------------------------- 
    28    REAL(wp), DIMENSION(jpi,jpj,jpk) ::   & 
     23   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   &   !: 
    2924      ! before !  now      !  after  ! 
    3025      ub       ,  un       ,  ua     ,   &  !: i-horizontal velocity (m/s) 
     
    3530      tb       ,  tn       ,  ta     ,   &  !: potential temperature (celcius) 
    3631      sb       ,  sn       ,  sa            !: salinity (psu) 
    37    REAL(wp), DIMENSION(jpi,jpj,jpk) ::   & 
     32   REAL(wp), PUBLIC, DIMENSION(jpi,jpj,jpk) ::   &   !: 
    3833      rhd ,                              &  !: in situ density anomalie rhd=(rho-rau0)/rau0 (no units) 
    3934      rhop,                              &  !: potential volumic mass (kg/m3) 
     
    4237   !! surface pressure gradient 
    4338   !! ------------------------- 
    44    REAL(wp), DIMENSION(jpi,jpj) ::   & 
     39   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   &   !: 
    4540      spgu, spgv             !: horizontal surface pressure gradient 
    4641 
     
    4843   !! interpolated gradient 
    4944   !! --------------------- 
    50    REAL(wp), DIMENSION(jpi,jpj) ::   & 
     45   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   &   !: 
    5146      gtu, gsu, gru,      &  !: t-, s- and rd horizontal gradient at u- and  
    5247      gtv, gsv, grv          !: v-points at bottom ocean level  
    5348#else 
    54    REAL(wp) ::   & 
     49   REAL(wp), PUBLIC ::   &   !: 
    5550      gtu, gsu, gru,      &  !: dummy scalars 
    5651      gtv, gsv, grv          !: 
     
    6055   !! free surface - constant volume formulation 
    6156   !! ------------------------------------------ 
    62    REAL(wp), DIMENSION(jpi,jpj) ::   & 
     57   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   &   !: 
    6358      sshb, sshn,         &  !: before, now sea surface height (meters) 
    6459      hu, hv                 !: depth at u- and v-points (meters) 
    6560# if defined key_obc 
    66    REAL(wp) obcsurftot       !: Total lateral surface of open boundaries 
    67    REAL(wp), DIMENSION(jpi,jpj) ::   & 
     61   REAL(wp), PUBLIC ::    &  !: 
     62      obcsurftot       !: Total lateral surface of open boundaries 
     63   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   &   !: 
    6864      obcumask, obcvmask     !: u-, v- Force filtering mask for the open  
    6965      !                      !  boundary condition on grad D 
     
    7369   !! rigid-lid formulation 
    7470   !! --------------------- 
    75    REAL(wp), DIMENSION(jpi,jpj) ::   & 
     71   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   &   !: 
    7672      hur, hvr,           &  !: inverse of u and v-points ocean depth (1/m) 
    7773      bsfb, bsfn,         &  !: before, now barotropic streamfunction (m3/s) 
  • trunk/NEMO/OPA_SRC/ocfzpt.F90

    r3 r15  
    1717 
    1818   !! * Shared module variables    
    19    REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   & 
     19   REAL(wp), PUBLIC, DIMENSION(jpi,jpj) ::   &  !: 
    2020      freeze, freezn,  &  !: after and now ice mask (0 or 1) 
    2121      fzptb, fzptn        !: before and now freezing point 
  • trunk/NEMO/OPA_SRC/opa.F90

    r3 r15  
    106106         OPEN( UNIT=numout, FILE='ocean.output', FORM='FORMATTED' ) 
    107107      ENDIF 
    108 #if defined key_mpp 
    109       OPEN( UNIT=nummpp, FILE='mpp.output', FORM='FORMATTED' ) 
    110 #endif 
     108      IF( lk_mpp )   OPEN( UNIT=nummpp, FILE='mpp.output', FORM='FORMATTED' ) 
    111109 
    112110 
     
    222220      ENDIF 
    223221 
    224 #if defined key_mpp 
    225       CALL mppstop                          ! Close all files (mpp) 
    226 #endif 
     222      IF( lk_mpp )   CALL mppstop                          ! Close all files (mpp) 
    227223 
    228224   END SUBROUTINE opa_model 
     225 
    229226 
    230227   SUBROUTINE opa_flg 
  • trunk/NEMO/OPA_SRC/par_EEL_R2.h90

    r3 r15  
    33   !!   Ocean Domain : 2 km resolution Channel (EEL_R2 configuration) 
    44   !!--------------------------------------------------------------------- 
    5    CHARACTER (len=16), PARAMETER ::   & 
    6       cp_cfg = "eel"            ! name of the configuration 
    7    INTEGER, PARAMETER ::     & 
    8       jp_cfg = 2   ,         &  ! resolution of the configuration (km) 
     5   CHARACTER (len=16), PARAMETER ::   &  !: 
     6      cp_cfg = "eel"            !: name of the configuration 
     7   INTEGER, PARAMETER ::     &  !: 
     8      jp_cfg = 2   ,         &  !: resolution of the configuration (km) 
    99 
    1010      ! data size              !!! * size of all the input files * 
    11       jpidta  = 83,          &  ! 1st horizontal dimension ( >= jpi ) 
    12       jpjdta  = 242,         &  ! 2nd    "            "    ( >= jpj ) 
    13       jpkdta  = 30,          &  ! number of levels         ( >= jpk ) 
     11      jpidta  = 83,          &  !: 1st horizontal dimension ( >= jpi ) 
     12      jpjdta  = 242,         &  !: 2nd    "            "    ( >= jpj ) 
     13      jpkdta  = 30,          &  !: number of levels         ( >= jpk ) 
    1414 
    1515      ! global domain size     !!! * full domain * 
    16       jpiglo  = jpidta,      &  ! 1st dimension of global domain --> i 
    17       jpjglo  = jpjdta,      &  ! 2nd    "                  "    --> j 
    18       jpk     = jpkdta,      &  ! number of vertical levels 
     16      jpiglo  = jpidta,      &  !: 1st dimension of global domain --> i 
     17      jpjglo  = jpjdta,      &  !: 2nd    "                  "    --> j 
     18      jpk     = jpkdta,      &  !: number of vertical levels 
    1919      ! zoom starting position 
    20       jpizoom =   1   ,      &  ! left bottom (i,j) indices of the zoom 
    21       jpjzoom =   1   ,      &  ! in data indices 
     20      jpizoom =   1   ,      &  !: left bottom (i,j) indices of the zoom 
     21      jpjzoom =   1   ,      &  !: in data indices 
    2222 
    2323      ! Domain characteristics 
    24       jperio  =     1 ,      &  ! lateral cond. type (between 0 and 6) 
    25       jpisl   =     1 ,      &  ! number of islands 
    26       jpnisl  = jpiglo          ! maximum number of points per island 
     24      jperio  =     1 ,      &  !: lateral cond. type (between 0 and 6) 
     25      jpisl   =     1 ,      &  !: number of islands 
     26      jpnisl  = jpiglo          !: maximum number of points per island 
    2727 
    2828   !!  Values set to pp_not_used indicates that this parameter is not used in THIS config. 
    2929   !!  Values set to pp_to_be_computed  indicates that variables will be computed in domzgr 
    30    REAL(wp), PARAMETER      ::  pp_not_used = 999999_wp  , & 
    31       &                    pp_to_be_computed = 0._wp 
     30   REAL(wp), PARAMETER ::   &  !: 
     31      pp_not_used       = 999999._wp  , & !: ??? 
     32      pp_to_be_computed =      0._wp      !: ??? 
    3233   !! 
    3334   !! Coefficients associated with the horizontal coordinate system (jphgr_msh /= 0 ) 
    3435   !! 
    35    INTEGER,PARAMETER   ::    & ! 
    36       jphgr_msh = 3            ! type of horizontal mesh 
     36   INTEGER,PARAMETER   ::    & !: 
     37      jphgr_msh = 3            !: type of horizontal mesh 
    3738      !                        ! = 0 curvilinear coordinate on the sphere 
    3839      !                        !     read in coordinate.nc file 
     
    4748      !   The mercator grid starts only approximately at gphi0 because 
    4849      !   of the constraint that the equator be a T point. 
    49    REAL(wp) ,PARAMETER ::     &  ! 
    50       ppglam0  =    0.0_wp,   &  ! longitude of first raw and column T-point (jphgr_msh = 1) 
    51       ppgphi0  =  -35.0_wp,   &  ! latitude  of first raw and column T-point (jphgr_msh = 1) 
     50   REAL(wp) ,PARAMETER ::     &  !: 
     51      ppglam0  =    0.0_wp,   &  !: longitude of first raw and column T-point (jphgr_msh = 1) 
     52      ppgphi0  =  -35.0_wp,   &  !: latitude  of first raw and column T-point (jphgr_msh = 1) 
    5253      !                          ! latitude for the Coriolis or Beta parameter (jphgr_msh = 2 or 3) 
    53       ppe1_deg = pp_not_used ,   &  ! zonal      grid-spacing (degrees) 
    54       ppe2_deg = pp_not_used ,   &  ! meridional grid-spacing (degrees) 
     54      ppe1_deg = pp_not_used ,   &  !: zonal      grid-spacing (degrees) 
     55      ppe2_deg = pp_not_used ,   &  !: meridional grid-spacing (degrees) 
    5556      ! 
    56       ppe1_m   = 2000.0_wp,   &  ! zonal      grid-spacing (meters ) 
    57       ppe2_m   = 2000.0_wp       ! meridional grid-spacing (meters ) 
     57      ppe1_m   = 2000.0_wp,   &  !: zonal      grid-spacing (meters ) 
     58      ppe2_m   = 2000.0_wp       !: meridional grid-spacing (meters ) 
    5859   !! 
    5960   !!  Coefficients associated with the vertical coordinate system 
    6061   !! 
    6162 
    62    REAL(wp), PARAMETER  ::       & 
    63       &     ppsur = -2033.194295283385_wp   ,  &  ! Computed in domzgr 
    64       &     ppa0  =  155.8325369664153_wp   ,  &  ! 
    65       &     ppa1  =  146.3615918601890_wp   ,  &  ! 
     63   REAL(wp), PARAMETER  ::       &  !: 
     64      &     ppsur = -2033.194295283385_wp   ,  &  !: Computed in domzgr 
     65      &     ppa0  =  155.8325369664153_wp   ,  &  !: 
     66      &     ppa1  =  146.3615918601890_wp   ,  &  !: 
    6667      ! 
    67       &     ppkth =  17.28520372419791_wp   ,  &  ! (non dimensional): gives the approximate 
     68      &     ppkth =  17.28520372419791_wp   ,  &  !: (non dimensional): gives the approximate 
    6869      !                                           !    layer number above which  stretching will 
    6970      !                                           !    be maximum. Usually of order jpk/2. 
    70       &     ppacr =  5.000000000000000_wp         ! (non dimensional): stretching factor 
     71      &     ppacr =  5.000000000000000_wp         !: (non dimensional): stretching factor 
    7172      !                                           !    for the grid. The highest zacr, the smallest 
    7273      !                                           !    the stretching. 
     
    7677   !!  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
    7778   !! 
    78    REAL(wp), PARAMETER ::        & 
    79       &     ppdzmin = pp_not_used              ,  &  ! (meters): depth of the top (first) model layer 
     79   REAL(wp), PARAMETER ::        &   !: 
     80      &     ppdzmin = pp_not_used              ,  &  !: (meters): depth of the top (first) model layer 
    8081      !                                           !           depth of second "w" level 
    81       &     pphmax  = pp_not_used                    ! (meters):  maximum depth of the ocean 
     82      &     pphmax  = pp_not_used                    !: (meters):  maximum depth of the ocean 
    8283      !                                           !            depth of the last "w" level 
    8384 
  • trunk/NEMO/OPA_SRC/par_EEL_R5.h90

    r3 r15  
    33   !!   Ocean Domain : 5 km resolution Channel (EEL_R5 configuration) 
    44   !!--------------------------------------------------------------------- 
    5    CHARACTER (len=16), PARAMETER ::   & 
    6       cp_cfg = "eel"            ! name of the configuration 
    7    INTEGER, PARAMETER ::     & 
    8       jp_cfg = 5      ,      &  ! resolution of the configuration (km) 
     5   CHARACTER (len=16), PARAMETER ::   &  !: 
     6      cp_cfg = "eel"            !: name of the configuration 
     7   INTEGER, PARAMETER ::     &  !: 
     8      jp_cfg = 5      ,      &  !: resolution of the configuration (km) 
    99 
    1010      ! data size              !!! * size of all the input files 
    11       jpidta  = 202   ,      &  ! first horizontal dimension > or = to jpi 
    12       jpjdta  = 104   ,      &  ! second                     > or = to jpj 
    13       jpkdta  =  40   ,      &  ! number of levels           > or = to jpk 
     11      jpidta  = 202   ,      &  !: first horizontal dimension > or = to jpi 
     12      jpjdta  = 104   ,      &  !: second                     > or = to jpj 
     13      jpkdta  =  40   ,      &  !: number of levels           > or = to jpk 
    1414 
    1515      ! total domain size      !!! * full domain * 
    16       jpiglo  = jpidta,      &  ! first  dimension of global domain --> i 
    17       jpjglo  = jpjdta,      &  ! second dimension of global domain --> j 
    18       jpk     = jpkdta,      &  ! number of vertical levels 
     16      jpiglo  = jpidta,      &  !: first  dimension of global domain --> i 
     17      jpjglo  = jpjdta,      &  !: second dimension of global domain --> j 
     18      jpk     = jpkdta,      &  !: number of vertical levels 
    1919      ! zoom starting position 
    20       jpizoom =   1   ,      &  ! left bottom (i,j) indices of the zoom 
    21       jpjzoom =   1   ,      &  ! in data indices 
     20      jpizoom =   1   ,      &  !: left bottom (i,j) indices of the zoom 
     21      jpjzoom =   1   ,      &  !: in data indices 
    2222 
    2323      ! Domain characteristics 
    24       jperio  =   0   ,      &  ! lateral cond. type (between 0 and 6) 
    25       jpisl   =   1   ,      &  ! number of islands 
    26       jpnisl  = jpiglo          ! maximum number of points per island 
     24      jperio  =   0   ,      &  !: lateral cond. type (between 0 and 6) 
     25      jpisl   =   1   ,      &  !: number of islands 
     26      jpnisl  = jpiglo          !: maximum number of points per island 
    2727 
    2828   !!  Values set to pp_not_used indicates that this parameter is not used in THIS config. 
    2929   !!  Values set to pp_to_be_computed  indicates that variables will be computed in domzgr 
    30    REAL(wp), PARAMETER ::   & 
     30   REAL(wp), PARAMETER ::   &  !: 
    3131      pp_not_used       = 999999._wp ,  &  !: 
    3232      pp_to_be_computed =      0._wp       !: 
     
    3434   !! Coefficients associated with the horizontal coordinate system (jphgr_msh /= 0 ) 
    3535 
    36    INTEGER,PARAMETER   ::    & ! 
    37       jphgr_msh = 2            ! type of horizontal mesh 
     36   INTEGER,PARAMETER   ::    & !: 
     37      jphgr_msh = 2            !: type of horizontal mesh 
    3838      !                        ! = 0 curvilinear coordinate on the sphere 
    3939      !                        !     read in coordinate.nc file 
     
    4848      !   The mercator grid starts only approximately at gphi0 because 
    4949      !   of the constraint that the equator be a T point. 
    50    REAL(wp) ,PARAMETER ::     &  ! 
    51       ppglam0  =    0.0_wp,   &  ! longitude of first raw and column T-point (jphgr_msh = 1) 
    52       ppgphi0  =  -35.0_wp,   &  ! latitude  of first raw and column T-point (jphgr_msh = 1) 
     50   REAL(wp) ,PARAMETER ::     &  !: 
     51      ppglam0  =    0.0_wp,   &  !: longitude of first raw and column T-point (jphgr_msh = 1) 
     52      ppgphi0  =  -35.0_wp,   &  !: latitude  of first raw and column T-point (jphgr_msh = 1) 
    5353      !                          ! latitude for the Coriolis or Beta parameter (jphgr_msh = 2 or 3) 
    54       ppe1_deg = pp_not_used,   &  ! zonal      grid-spacing (degrees) 
    55       ppe2_deg = pp_not_used,   &  ! meridional grid-spacing (degrees) 
     54      ppe1_deg = pp_not_used,   &  !: zonal      grid-spacing (degrees) 
     55      ppe2_deg = pp_not_used,   &  !: meridional grid-spacing (degrees) 
    5656      ! 
    57       ppe1_m   = 5000.0_wp,   &  ! zonal      grid-spacing (meters) 
    58       ppe2_m   = 5000.0_wp       ! meridional grid-spacing (meters) 
     57      ppe1_m   = 5000.0_wp,   &  !: zonal      grid-spacing (meters) 
     58      ppe2_m   = 5000.0_wp       !: meridional grid-spacing (meters) 
    5959   !! 
    6060   !!  Coefficients associated with the vertical coordinate system 
    6161   !! 
    62    REAL(wp), PARAMETER  ::       & 
    63       &     ppsur = pp_to_be_computed       ,  &  ! Computed in domzgr, set ppdzmin, pphmax below 
    64       &     ppa0  = pp_to_be_computed       ,  &  ! 
    65       &     ppa1  = pp_to_be_computed       ,  &  ! 
     62   REAL(wp), PARAMETER  ::       &   !: 
     63      &     ppsur = pp_to_be_computed       ,  &  !: Computed in domzgr, set ppdzmin, pphmax below 
     64      &     ppa0  = pp_to_be_computed       ,  &  !: 
     65      &     ppa1  = pp_to_be_computed       ,  &  !: 
    6666      ! 
    67       &     ppkth = 20._wp                  ,  &  ! (non dimensional): gives the approximate 
     67      &     ppkth = 20._wp                  ,  &  !: (non dimensional): gives the approximate 
    6868      !                                           !    layer number above which  stretching will 
    6969      !                                           !    be maximum. Usually of order jpk/2. 
    70       &     ppacr = 16.00000000000_wp             ! (non dimensional): stretching factor 
     70      &     ppacr = 16.00000000000_wp             !: (non dimensional): stretching factor 
    7171      !                                           !    for the grid. The highest zacr, the smallest 
    7272      !                                           !    the stretching. 
     
    7676   !!  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
    7777   !! 
    78    REAL(wp), PARAMETER ::        & 
    79       &     ppdzmin = 120._wp               ,  &  ! (meters): depth of the top (first) model layer 
     78   REAL(wp), PARAMETER ::        &  !: 
     79      &     ppdzmin = 120._wp               ,  &  !: (meters): depth of the top (first) model layer 
    8080      !                                           !           depth of second "w" level 
    81       &     pphmax  = 4000._wp                    ! (meters):  maximum depth of the ocean 
     81      &     pphmax  = 4000._wp                    !: (meters):  maximum depth of the ocean 
    8282      !                                           !            depth of the last "w" level 
    8383   !!--------------------------------------------------------------------- 
  • trunk/NEMO/OPA_SRC/par_EEL_R6.h90

    r3 r15  
    33   !!   Ocean Domain : 6 km resolution Channel (EEL_R6 configuration) 
    44   !!--------------------------------------------------------------------- 
    5    CHARACTER (len=16), PARAMETER ::   & 
    6       cp_cfg = "eel"            ! name of the configuration 
    7    INTEGER, PARAMETER ::     & 
    8       jp_cfg = 6      ,      &  ! resolution of the configuration (km) 
     5   CHARACTER (len=16), PARAMETER ::   &  !: 
     6      cp_cfg = "eel"            !: name of the configuration 
     7   INTEGER, PARAMETER ::     &  !: 
     8      jp_cfg = 6      ,      &  !: resolution of the configuration (km) 
    99 
    1010      ! data size              !!! * size of all the input files * 
    11       jpidta  = 29,          &  ! 1st lateral dimension ( >= jpi ) 
    12       jpjdta  = 83,          &  ! 2nd    "         "    ( >= jpj ) 
    13       jpkdta  = 30,          &  ! number of levels      ( >= jpk ) 
     11      jpidta  = 29,          &  !: 1st lateral dimension ( >= jpi ) 
     12      jpjdta  = 83,          &  !: 2nd    "         "    ( >= jpj ) 
     13      jpkdta  = 30,          &  !: number of levels      ( >= jpk ) 
    1414 
    1515      ! global domain size     !!! * full domain * 
    16       jpiglo  = jpidta,      &  ! 1st dimension of global domain --> i 
    17       jpjglo  = jpjdta,      &  ! 2nd    "                  "    --> j 
    18       jpk     = jpkdta,      &  ! number of vertical levels 
     16      jpiglo  = jpidta,      &  !: 1st dimension of global domain --> i 
     17      jpjglo  = jpjdta,      &  !: 2nd    "                  "    --> j 
     18      jpk     = jpkdta,      &  !: number of vertical levels 
    1919      ! starting position of the zoom 
    20       jpizoom =   1   ,      &  ! left bottom (i,j) indices of the zoom 
    21       jpjzoom =   1   ,      &  ! in data domain indices 
     20      jpizoom =   1   ,      &  !: left bottom (i,j) indices of the zoom 
     21      jpjzoom =   1   ,      &  !: in data domain indices 
    2222 
    2323      ! Domain characteristics 
    24       jperio  =      1,      &  ! lateral cond. type (between 0 and 6) 
    25       jpisl   =      1,      &  ! number of islands 
    26       jpnisl  = jpiglo          ! maximum number of points per island 
     24      jperio  =      1,      &  !: lateral cond. type (between 0 and 6) 
     25      jpisl   =      1,      &  !: number of islands 
     26      jpnisl  = jpiglo          !: maximum number of points per island 
    2727 
    2828   !!  Values set to pp_not_used indicates that this parameter is not used in THIS config. 
    2929   !!  Values set to pp_to_be_computed  indicates that variables will be computed in domzgr 
    30    REAL(wp), PARAMETER      ::  pp_not_used = 999999_wp , & 
    31       &                    pp_to_be_computed = 0._wp 
    32    !! 
     30   REAL(wp), PARAMETER ::   &  !: 
     31      pp_not_used       = 999999._wp ,  &  !: ??? 
     32      pp_to_be_computed =      0._wp       !: ??? 
     33 
    3334   !! Coefficients associated with the horizontal coordinate system (jphgr_msh /= 0 ) 
    34    !! 
    3535 
    36    INTEGER,PARAMETER   ::    & ! 
    37       jphgr_msh = 3            ! type of horizontal mesh 
     36   INTEGER,PARAMETER   ::    & !: 
     37      jphgr_msh = 3            !: type of horizontal mesh 
    3838      !                        ! = 0 curvilinear coordinate on the sphere 
    3939      !                        !     read in coordinate.nc file 
     
    4848      !   The mercator grid starts only approximately at gphi0 because 
    4949      !   of the constraint that the equator be a T point. 
    50    REAL(wp) ,PARAMETER ::     &  ! 
    51       ppglam0  =    0.0_wp,   &  ! longitude of first raw and column T-point (jphgr_msh = 1) 
    52       ppgphi0  =  -35.0_wp,   &  ! latitude  of first raw and column T-point (jphgr_msh = 1) 
    53       !                          ! latitude for the Coriolis or Beta parameter (jphgr_msh = 2 or 3) 
    54       ppe1_deg = pp_not_used,   &  ! zonal      grid-spacing (degrees) 
    55       ppe2_deg = pp_not_used,   &  ! meridional grid-spacing (degrees) 
     50   REAL(wp) ,PARAMETER ::     &  !: 
     51      ppglam0  =    0.0_wp,   &  !: longitude of first raw and column T-point (jphgr_msh = 1) 
     52      ppgphi0  =  -35.0_wp,   &  !: latitude  of first raw and column T-point (jphgr_msh = 1) 
     53      !                          !  latitude for the Coriolis or Beta parameter (jphgr_msh = 2 or 3) 
     54      ppe1_deg = pp_not_used,   &  !: zonal      grid-spacing (degrees) 
     55      ppe2_deg = pp_not_used,   &  !: meridional grid-spacing (degrees) 
    5656      ! 
    57       ppe1_m   = 6000.0_wp,   &  ! zonal      grid-spacing (meters ) 
    58       ppe2_m   = 6000.0_wp       ! meridional grid-spacing (meters ) 
    59    !! 
     57      ppe1_m   = 6000.0_wp,   &  !: zonal      grid-spacing (meters ) 
     58      ppe2_m   = 6000.0_wp       !: meridional grid-spacing (meters ) 
     59 
    6060   !!  Coefficients associated with the vertical coordinate system 
    61    !! 
    62    REAL(wp), PARAMETER  ::       & 
    63       &     ppsur = -2033.194295283385_wp   ,  &  ! Computed in domzgr 
    64       &     ppa0  =  155.8325369664153_wp   ,  &  ! 
    65       &     ppa1  =  146.3615918601890_wp   ,  &  ! 
     61 
     62   REAL(wp), PARAMETER  ::       &  !: 
     63      &     ppsur = -2033.194295283385_wp   ,  &  !: Computed in domzgr 
     64      &     ppa0  =  155.8325369664153_wp   ,  &  !: 
     65      &     ppa1  =  146.3615918601890_wp   ,  &  !: 
    6666      ! 
    67       &     ppkth =  17.28520372419791_wp   ,  &  ! (non dimensional): gives the approximate 
    68       !                                           !    layer number above which  stretching will 
    69       !                                           !    be maximum. Usually of order jpk/2. 
    70       &     ppacr =  5.000000000000000_wp         ! (non dimensional): stretching factor 
    71       !                                           !    for the grid. The highest zacr, the smallest 
    72       !                                           !    the stretching. 
     67      &     ppkth =  17.28520372419791_wp   ,  &  !: (non dimensional): gives the approximate 
     68      !                                           !     layer number above which  stretching will 
     69      !                                           !     be maximum. Usually of order jpk/2. 
     70      &     ppacr =  5.000000000000000_wp         !: (non dimensional): stretching factor 
     71      !                                           !     for the grid. The highest zacr, the smallest 
     72      !                                           !     the stretching. 
    7373 
    74    !! 
     74 
    7575   !!  If both ppa0 ppa1 and ppsur are specified to 0, then 
    7676   !!  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
    77    !! 
    78    REAL(wp), PARAMETER ::        & 
    79       &     ppdzmin = pp_not_used           ,  &  ! (meters): depth of the top (first) model layer 
    80       !                                           !           depth of second "w" level 
    81       &     pphmax  = pp_not_used                 ! (meters):  maximum depth of the ocean 
    82       !                                           !            depth of the last "w" level 
     77 
     78   REAL(wp), PARAMETER ::        &  !: 
     79      &     ppdzmin = pp_not_used           ,  &  !: (meters): depth of the top (first) model layer 
     80      !                                           !            depth of second "w" level 
     81      &     pphmax  = pp_not_used                 !: (meters):  maximum depth of the ocean 
     82      !                                           !             depth of the last "w" level 
    8383   !!--------------------------------------------------------------------- 
  • trunk/NEMO/OPA_SRC/par_kind.F90

    r3 r15  
    1313   PRIVATE 
    1414 
    15    INTEGER, PUBLIC, PARAMETER ::    & 
     15   INTEGER, PUBLIC, PARAMETER ::    &  !: 
    1616      jpbyt   = 8       ,           &  !: real size for mpp communications 
    1717      jpbytda = 4       ,           &  !: real size in input data files 4 or 8 
     
    2525   !            exponent = 37     exponent = 307 
    2626 
    27    INTEGER, PUBLIC, PARAMETER ::        &  !  Floating point section 
    28       sp = SELECTED_REAL_KIND(6,37)  ,  &  !: single precision (real 4) 
     27   INTEGER, PUBLIC, PARAMETER ::        &  !: Floating point section 
     28      sp = SELECTED_REAL_KIND( 6, 37),  &  !: single precision (real 4) 
    2929      dp = SELECTED_REAL_KIND(12,307),  &  !: double precision (real 8) 
    3030      wp = dp                              !: working precision 
    3131 
    32    INTEGER, PUBLIC, PARAMETER ::        &  !  Integer section 
     32   INTEGER, PUBLIC, PARAMETER ::        &  !: Integer section 
    3333      i4 = SELECTED_INT_KIND(9) ,       &  !: single precision (integer 4) 
    3434      i8 = SELECTED_INT_KIND(14)           !: double precision (integer 8) 
  • trunk/NEMO/OPA_SRC/par_oce.F90

    r3 r15  
    1111   !!---------------------------------------------------------------------- 
    1212   !! * Modules used 
    13    USE par_kind          !: kind parameters 
     13   USE par_kind          ! kind parameters 
    1414 
    1515   IMPLICIT NONE 
     
    2222   !!      so jpiglo=jpi and jpjglo=jpj 
    2323 
    24    INTEGER, PARAMETER ::            & 
     24   INTEGER, PUBLIC, PARAMETER ::    &  !: 
    2525      jpni   = 1,                   &  !: number of processors following i  
    2626      jpnj   = 1,                   &  !: number of processors following j 
     
    7575   !!   default option  :                               small closed basin 
    7676   !!--------------------------------------------------------------------- 
    77    CHARACTER (len=16), PARAMETER :: & 
     77   CHARACTER(len=16), PUBLIC, PARAMETER ::   &  !: 
    7878      cp_cfg = "default"               !: name of the configuration 
    79    INTEGER, PARAMETER ::            & 
     79   INTEGER, PARAMETER ::            &  !: 
    8080      jp_cfg = 0  ,                 &  !: resolution of the configuration 
    8181 
     
    9898      jpnisl  =  0                     !: maximum number of points per island 
    9999 
     100      !!  Values set to pp_not_used indicates that this parameter is not used in THIS config. 
     101      !!  Values set to pp_to_be_computed  indicates that variables will be computed in domzgr 
     102      REAL(wp), PARAMETER ::   &  !: 
     103         pp_not_used       = 999999._wp , &  !: 
     104         pp_to_be_computed = 999999._wp      !: 
     105 
     106 
    100107   !! Horizontal grid parameters for domhgr 
    101108   !! ===================================== 
    102109 
    103    INTEGER, PARAMETER   ::   & ! 
     110   INTEGER, PUBLIC, PARAMETER   ::   &  !: 
    104111      jphgr_msh = 0            !: type of horizontal mesh 
    105112      !                        !  = 0 curvilinear coordinate on the sphere 
     
    112119      !                        !      isotropic resolution (e1_deg) 
    113120 
    114    REAL(wp) , PARAMETER ::    &  ! 
     121   REAL(wp) , PUBLIC, PARAMETER ::   &   !: 
    115122      ppglam0  =    0.0_wp,   &  !: longitude of first raw and column T-point (jphgr_msh = 1) 
    116123      ppgphi0  =  -35.0_wp,   &  !: latitude  of first raw and column T-point (jphgr_msh = 1) 
     
    121128      ppe2_m   = 5000.0_wp       !: meridional grid-spacing (degrees) 
    122129 
    123  
    124    !! 
    125130   !! Vertical grid parameter for domzgr 
    126131   !! ================================== 
    127    !! 
    128    REAL(wp), PARAMETER  ::       & 
    129       &     ppsur = -4762.96143546300_wp    ,  &  !: ORCA r4, r2 and r05 coefficients 
    130       &     ppa0  =   255.58049070440_wp    ,  &  !: (default coefficients) 
    131       &     ppa1  =   245.58132232490_wp    ,  &  !: 
    132       &     ppkth =    21.43336197938_wp    ,  &  !: 
    133       &     ppacr =     3.00000000000_wp          !: 
     132 
     133   REAL(wp), PUBLIC, PARAMETER  ::   &  !: 
     134      &     ppsur = -4762.96143546300_wp ,  &  !: ORCA r4, r2 and r05 coefficients 
     135      &     ppa0  =   255.58049070440_wp ,  &  !: (default coefficients) 
     136      &     ppa1  =   245.58132232490_wp ,  &  !: 
     137      &     ppkth =    21.43336197938_wp ,  &  !: 
     138      &     ppacr =     3.00000000000_wp       !: 
    134139 
    135140   !!  If both ppa0 ppa1 and ppsur are specified to 0, then 
    136141   !!  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
    137142 
    138    REAL(wp), PARAMETER ::        & 
    139       &     ppdzmin = 10._wp                ,  &  !: Minimum vertical spacing 
    140       &     pphmax  = 5000._wp                    !: Maximum depth 
     143   REAL(wp), PUBLIC, PARAMETER ::   &  !: 
     144      &     ppdzmin = 10._wp             ,  &  !: Minimum vertical spacing 
     145      &     pphmax  = 5000._wp                 !: Maximum depth 
    141146 
    142147   !!--------------------------------------------------------------------- 
     
    146151   !! Domain Matrix size 
    147152   !!--------------------------------------------------------------------- 
    148    INTEGER, PARAMETER ::            & 
    149       jpi = ( jpiglo-2*jpreci + (jpni-1) ) / jpni + 2*jpreci ,   & 
    150       !                                !: first  dimension of grid --> i 
    151       jpj = ( jpjglo-2*jprecj + (jpnj-1) ) / jpnj + 2*jprecj ,   & 
    152       !                                !: second dimension of grid --> j 
    153       jpim1 = jpi-1,                &  !:  jpi - 1 
    154       jpjm1 = jpj-1,                &  !:  jpj - 1 
    155       jpkm1 = jpk-1,                &  !:  jpk - 1 
    156       jpij  = jpi*jpj                  !:  jpi x jpj 
     153   INTEGER, PUBLIC, PARAMETER ::   &  !: 
     154      jpi = ( jpiglo-2*jpreci + (jpni-1) ) / jpni + 2*jpreci ,   &  !: first  dimension 
     155      jpj = ( jpjglo-2*jprecj + (jpnj-1) ) / jpnj + 2*jprecj ,   &  !: second dimension 
     156      jpim1 = jpi-1,                                             &  !: inner domain indices 
     157      jpjm1 = jpj-1,                                             &  !:   "            " 
     158      jpkm1 = jpk-1,                                             &  !:   "            " 
     159      jpij  = jpi*jpj                                               !:  jpi x jpj 
    157160 
    158161   !!--------------------------------------------------------------------- 
    159    !! ESOPA control 
     162   !! Optimization/control flags 
    160163   !!--------------------------------------------------------------------- 
    161164#if defined key_esopa 
    162    LOGICAL, PARAMETER ::   lk_esopa = .TRUE.   !: flag to activate the all options 
     165   LOGICAL, PUBLIC, PARAMETER ::   lk_esopa    = .TRUE.   !: flag to activate the all options 
    163166#else 
    164    LOGICAL, PARAMETER ::   lk_esopa = .FALSE.  !: flag to activate the all options 
     167   LOGICAL, PUBLIC, PARAMETER ::   lk_esopa     = .FALSE.  !: flag to activate the all options 
     168#endif 
     169 
     170#if defined key_vectopt_memory 
     171   LOGICAL, PUBLIC, PARAMETER ::   lk_vopt_mem  = .TRUE.   !: vector optimization flag 
     172#else 
     173   LOGICAL, PUBLIC, PARAMETER ::   lk_vopt_mem  = .FALSE.  !: vector optimization flag 
     174#endif 
     175 
     176#if defined key_vectopt_loop 
     177   LOGICAL, PUBLIC, PARAMETER ::   lk_vopt_loop = .TRUE.   !: vector optimization flag 
     178#else 
     179   LOGICAL, PUBLIC, PARAMETER ::   lk_vopt_loop = .FALSE.  !: vector optimization flag 
    165180#endif 
    166181 
  • trunk/NEMO/OPA_SRC/phycst.F90

    r3 r15  
    1515 
    1616   !! * Shared module variables 
    17    INTEGER, PUBLIC, DIMENSION(12) ::   & 
     17   INTEGER, PUBLIC, DIMENSION(12) ::   &  !: 
    1818      nbiss = (/ 31, 29, 31, 30, 31, 30,      &  !: number of days per month 
    1919         &       31, 31, 30, 31, 30, 31 /) ,  &  !  (leap-year) 
     
    2121         &       31, 31, 30, 31, 30, 31 /)       !  (365 days a year) 
    2222    
    23    REAL(wp), PUBLIC ::                        & 
     23   REAL(wp), PUBLIC ::                        &  !: 
    2424      rpi = 3.141592653589793_wp           ,  &  !: pi 
    2525      rad = 3.141592653589793_wp / 180._wp ,  &  !: conversion from degre into radian 
    2626      rsmall = 0.5 * EPSILON( 1. )               !: smallest real computer value 
    2727    
    28    REAL(wp), PUBLIC ::          & 
     28   REAL(wp), PUBLIC ::          & !: 
    2929      rday = 24.*60.*60.  ,     & !: day (s) 
    3030      rsiyea              ,     & !: sideral year (s) 
     
    4141      omega               ,    &  !: earth rotation parameter 
    4242      ra    = 6371229._wp ,    &  !: earth radius (meter) 
    43       g     = 9.80665_wp          !: gravity (m/s2) 
    44     
    45    REAL(wp), PUBLIC ::         & 
     43      grav  = 9.80665_wp          !: gravity (m/s2) 
     44    
     45   REAL(wp), PUBLIC ::         &  !: 
    4646      rtt      = 273.16_wp  ,  &  !: triple point of temperature (Kelvin) 
    4747      rt0      = 273.15_wp  ,  &  !: freezing point of water (Kelvin) 
     
    5353      ro0cpr                      !: = 1. / ( rau0 * rcp ) 
    5454 
    55    REAL(wp), PUBLIC ::            & 
     55   REAL(wp), PUBLIC ::            &  !: 
    5656      rcdsn   =   0.22_wp     ,   &  !: conductivity of the snow 
    5757      rcdic   =   2.034396_wp ,   &  !: conductivity of the ice 
     
    154154 
    155155      IF(lwp) WRITE(numout,*) 
    156       IF(lwp) WRITE(numout,*) ' earth radius ra = ', ra, ' m' 
    157       IF(lwp) WRITE(numout,*) ' gravity      g  = ', g , ' m/s2' 
     156      IF(lwp) WRITE(numout,*) ' earth radius ra   = ', ra, ' m' 
     157      IF(lwp) WRITE(numout,*) ' gravity      grav = ', grav , ' m/s2' 
    158158 
    159159      IF(lwp) WRITE(numout,*) 
  • trunk/NEMO/OPA_SRC/restart.F90

    r3 r15  
    4545#  include "restart_fdir.h90" 
    4646 
    47 #elif defined key_mpp 
    48    !!---------------------------------------------------------------------- 
    49    !!                       direct acces file one per processor 
    50    !!                  (merging/splitting is done off-line, eventually) 
     47#elif  ( defined key_mpp_mpi   ||   defined key_mpp_shmem ) 
     48   !!---------------------------------------------------------------------- 
     49   !!   'key_mpp_mpi'     OR      MPI massively parallel processing library 
     50   !!   'key_mpp_shmem'         SHMEM massively parallel processing library 
     51   !!---------------------------------------------------------------------- 
     52   !!                 direct acces file one per processor 
     53   !!          (merging/splitting is done off-line, eventually) 
    5154   !!----------------------------------------------------------------------- 
    5255#  include "restart_mpp.h90" 
     
    7982      LOGICAL ::   llbon 
    8083      CHARACTER (len=50) ::   clname, cln 
    81       INTEGER ::   & 
    82          ic, jc, itime 
    83       REAL(wp) :: zdate0, zinfo(10) 
    84  
    85       REAL(wp), DIMENSION(1) ::  & 
    86          zfice, zfblk                       ! used only in case of ice , bulk 
     84      INTEGER ::   ic, jc, itime 
     85      REAL(wp) ::   zdate0 
     86      REAL(wp), DIMENSION( 1) ::   zfice, zfblk   ! used only in case of ice & bulk 
     87      REAL(wp), DIMENSION(10) ::   zinfo(10) 
    8788      !!---------------------------------------------------------------------- 
    8889      !!  OPA 8.5, LODYC-IPSL (2002) 
  • trunk/NEMO/OPA_SRC/restart_mpp.h90

    r3 r15  
    1   SUBROUTINE rst_write(kt) 
    2     !!--------------------------------------------------------------------- 
    3     !!                  ***  ROUTINE rst_write  *** 
    4     !!  
    5     !! ** Purpose :   Write restart fields in direct access format in mpp. 
    6     !!      one per process 
    7     !! 
    8     !! ** Method  :   each nstock time step , save fields which are necessary 
    9     !!      for restart 
    10     !!      Record #1 hold general information on the state of the run 
    11     !!      Data fields (either 3D or 2D ) starts ar record #2 
    12     !! 
    13     !! History : 
    14     !!        !  91-03  ()  original code 
    15     !!        !  91-11  (G. Madec) 
    16     !!        !  92-06  (M. Imbard)  correction restart file 
    17     !!        !  92-07  (M. Imbard)  split into diawri and rstwri 
    18     !!        !  98-02  (M. Guyon)  FETI method 
    19     !!        !  98-05  (G. Roullet)  free surface 
    20     !!        !  99-11  (M. Imbard)  NetCDF FORMAT with ioipsl 
    21     !!   8.5  !  03-06  (J.M. Molines)  F90: Free form, mpp support 
    22     !!---------------------------------------------------------------------- 
    23     !! * Arguments  
    24     INTEGER, INTENT( in ) ::   kt         ! ocean time-step 
    25  
    26     !! * Local declarations 
    27     INTEGER :: ino0, it0, ipcg0, isor0, itke0 
    28     INTEGER :: irecl8, irec 
    29     INTEGER :: ji,jj, jk 
    30     INTEGER :: inum = 11        ! temporary logical unit 
    31     INTEGER :: ios1 , ios2      ! flag for ice and bulk in the current run 
    32     INTEGER :: ios3             ! flag for free surface.  0 = none 1 = yes.  0 = none 1 = yes 
    33     INTEGER :: ios4             ! flag for coupled (1) or not (0) 
    34  
    35     CHARACTER(LEN=80)  :: clres 
    36     !!---------------------------------------------------------------------- 
    37     !!  OPA 8.5, LODYC-IPSL (2002) 
    38     !!---------------------------------------------------------------------- 
     1   !!--------------------------------------------------------------------- 
     2   !!                     ***  restart_mpp.h90  ***  
     3   !!--------------------------------------------------------------------- 
     4 
     5   SUBROUTINE rst_write(kt) 
     6     !!--------------------------------------------------------------------- 
     7     !!                  ***  ROUTINE rst_write  *** 
     8     !!  
     9     !! ** Purpose :   Write restart fields in direct access format in mpp. 
     10     !!      one per process 
     11     !! 
     12     !! ** Method  :   each nstock time step , save fields which are necessary 
     13     !!      for restart 
     14     !!      Record #1 hold general information on the state of the run 
     15     !!      Data fields (either 3D or 2D ) starts ar record #2 
     16     !! 
     17     !! History : 
     18     !!        !  91-03  ()  original code 
     19     !!        !  91-11  (G. Madec) 
     20     !!        !  92-06  (M. Imbard)  correction restart file 
     21     !!        !  92-07  (M. Imbard)  split into diawri and rstwri 
     22     !!        !  98-02  (M. Guyon)  FETI method 
     23     !!        !  98-05  (G. Roullet)  free surface 
     24     !!        !  99-11  (M. Imbard)  NetCDF FORMAT with ioipsl 
     25     !!   8.5  !  03-06  (J.M. Molines)  F90: Free form, mpp support 
     26     !!---------------------------------------------------------------------- 
     27     !! * Arguments  
     28     INTEGER, INTENT( in ) ::   kt         ! ocean time-step 
     29 
     30     !! * Local declarations 
     31     INTEGER :: ino0, it0, ipcg0, isor0, itke0 
     32     INTEGER :: irecl8, irec 
     33     INTEGER :: jk               ! dummy loop indices 
     34     INTEGER :: inum = 11        ! temporary logical unit 
     35     INTEGER :: ios1 , ios2      ! flag for ice and bulk in the current run 
     36     INTEGER :: ios3             ! flag for free surface.  0 = none 1 = yes.  0 = none 1 = yes 
     37     INTEGER :: ios4             ! flag for coupled (1) or not (0) 
     38 
     39     CHARACTER(LEN=80)  :: clres 
     40 
     41     REAL(wp), DIMENSION( 1) ::   zfice, zfblk   ! used only in case of ice & bulk 
     42     !!---------------------------------------------------------------------- 
     43     !!  OPA 8.5, LODYC-IPSL (2002) 
     44     !!---------------------------------------------------------------------- 
    3945 
    4046    IF( MOD( kt, nstock ) == 0 .OR. kt == nitend ) THEN 
     
    197203 
    198204#if defined key_ice_lim 
    199           WRITE(inum,REC=irec) fsst(:,:)  ; irec = irec + 1 
    200           WRITE(inum,REC=irec) fsss(:,:)  ; irec = irec + 1 
    201           WRITE(inum,REC=irec) fun (:,:)  ; irec = irec + 1 
    202           WRITE(inum,REC=irec) fvn (:,:)  ; irec = irec + 1 
     205          zfice(1) = FLOAT( nfice )                                      ! Louvain La Neuve Sea Ice Model 
     206          WRITE(inum,REC=irec) zfice(:)     ; irec = irec + 1 
     207          WRITE(inum,REC=irec) sst_io(:,:)  ; irec = irec + 1 
     208          WRITE(inum,REC=irec) sss_io(:,:)  ; irec = irec + 1 
     209          WRITE(inum,REC=irec) u_io  (:,:)  ; irec = irec + 1 
     210          WRITE(inum,REC=irec) v_io  (:,:)  ; irec = irec + 1 
    203211#    if defined key_coupled 
    204212          WRITE(inum,REC=irec) alb_ice(:,:)  ; irec = irec + 1 
     
    206214#endif 
    207215# if defined key_flx_bulk_monthly || defined key_flx_bulk_daily 
     216          zfblk(1) = FLOAT( nfbulk )                                 ! Bulk 
     217          WRITE(inum,REC=irec) zfblk(:)   ; irec = irec + 1 
    208218          WRITE(inum,REC=irec) gsst(:,:)  ; irec = irec + 1 
    209219# endif 
     
    245255    INTEGER :: irecl8, irec 
    246256    INTEGER :: ji,jj,jk 
    247     INTEGER :: ick, iwork, inum 
     257    INTEGER :: ick, inum 
    248258    INTEGER :: ios1, ios2, ios3, ios4 
    249259 
     
    251261 
    252262    LOGICAL   :: lstop 
     263 
     264      REAL(wp), DIMENSION( 1) ::   zfice, zfblk   ! used only in case of ice & bulk 
    253265 
    254266    !!---------------------------------------------------------------------- 
     
    330342 
    331343    ick = narea -iarea 
    332 #if defined key_mpp 
    333     CALL mpp_sum(ick) 
    334 #endif 
     344    CALL mpp_sum( ick ) 
    335345 
    336346    IF (ick /= 0 ) THEN 
     
    495505    ! check if it was in the previous run 
    496506    IF ( ios1 == 1 ) THEN 
    497        READ(inum,REC=irec) fsst(:,:) ; irec = irec + 1 
    498        READ(inum,REC=irec) fsss(:,:) ; irec = irec + 1 
    499        READ(inum,REC=irec) fun (:,:) ; irec = irec + 1 
    500        READ(inum,REC=irec) fvn (:,:) ; irec = irec + 1 
     507       READ(inum,REC=irec) zfice(:)    ; irec = irec + 1 
     508       READ(inum,REC=irec) sst_io(:,:) ; irec = irec + 1 
     509       READ(inum,REC=irec) sss_io(:,:) ; irec = irec + 1 
     510       READ(inum,REC=irec) u_io  (:,:) ; irec = irec + 1 
     511       READ(inum,REC=irec) v_io  (:,:) ; irec = irec + 1 
    501512#  if defined key_coupled 
    502513       READ(inum,REC=irec) alb_ice(:,:) ; irec = irec + 1 
    503514#  endif 
    504515    ENDIF 
    505     IF ( iice1 /= nfice .OR. ios1 == 0 ) THEN 
     516    IF ( zfice(1) /= FLOAT(nfice) .OR. ios1 == 0 ) THEN 
    506517         IF(lwp) WRITE(numout,*) 
    507518         IF(lwp) WRITE(numout,*) 'rst_read :  LLN sea Ice Model => Ice initialization' 
    508519         IF(lwp) WRITE(numout,*) 
    509          fsst(:,:) = 0. 
    510          fsss(:,:) = 0. 
    511          fun (:,:) = 0. 
    512          fvn (:,:) = 0. 
    513          fsst(:,:) = fsst(:,:) + ( nfice-1 )*( tn(:,:,1) + rt0 ) 
    514          fsss(:,:) = fsss(:,:) + ( nfice-1 )*  sn(:,:,1) 
     520         sst_io(:,:) = sst_io(:,:) + ( nfice-1 )*( tn(:,:,1) + rt0 ) 
     521         sss_io(:,:) = sss_io(:,:) + ( nfice-1 )*  sn(:,:,1) 
    515522         DO jj = 2, jpj 
    516523            DO ji = 2, jpi 
    517                fun(ji,jj) = fun(ji,jj) + (nfice-1)*0.5*( un(ji-1,jj,1)+un(ji-1,jj-1,1) ) 
    518                fvn(ji,jj) = fvn(ji,jj) + (nfice-1)*0.5*( vn(ji,jj-1,1)+vn(ji-1,jj-1,1) ) 
     524               u_io(ji,jj) = u_io(ji,jj) + (nfice-1)*0.5*( un(ji-1,jj,1)+un(ji-1,jj-1,1) ) 
     525               v_io(ji,jj) = v_io(ji,jj) + (nfice-1)*0.5*( vn(ji,jj-1,1)+vn(ji-1,jj-1,1) ) 
    519526            END DO 
    520527         END DO 
     
    528535      ! bulk forcing  
    529536      IF( ios2 == 1 ) THEN 
     537         READ(inum,REC=irec) zfblk(:)   ; irec = irec + 1 
    530538         READ(inum,REC=irec) gsst (:,:) ; irec = irec + 1 
    531539      ENDIF 
    532       IF( ibulk1 /= nfbulk  .OR. ios2 == 0 ) THEN 
     540      IF( zfblk(1) /= FLOAT(nfbulk)  .OR. ios2 == 0 ) THEN 
    533541         IF(lwp) WRITE(numout,*) 
    534542         IF(lwp) WRITE(numout,*) 'rst_read :  Bulk forcing ==> Initialization ' 
    535543         IF(lwp) WRITE(numout,*) 
    536          gsst(:,:) = 0. 
     544         gsst(:,:) = 0.e0 
    537545         gsst(:,:) = gsst(:,:) + ( nfbulk-1 )*( tn(:,:,1) + rt0 ) 
    538546      ENDIF 
  • trunk/NEMO/OPA_SRC/step.F90

    r3 r15  
    168168      !! * local declarations 
    169169      INTEGER ::   indic    ! error indicator if < 0 
     170      INTEGER ::   ii0, ii1, ij0, ij1   ! temporary integers 
    170171      !! --------------------------------------------------------------------- 
    171172 
     
    245246            CASE ( 05 )                         ! ORCA R2 configuration 
    246247               avt  (:,:,2) = avt  (:,:,2) + 1.e-3 * upsrnfh(:,:)   ! increase diffusivity of rivers mouths 
    247                IF( lk_zdfddm )   fsavs(:,:,2) = fsavs(:,:,2) + 1.e-3 * upsrnfh(:,:)    
    248248            CASE ( 2  )                         ! ORCA R2 configuration 
    249                avt( mi0(140):mi1(140) , mj0(102):mj1(102) , 2:jpkm1 ) =    &   ! Strait of Gibraltar 
    250                avt( mi0(140):mi1(140) , mj0(102):mj1(102) , 2:jpkm1 ) / 5.e0     
    251                avt( mi0(161):mi1(161) , mj0( 88):mj1( 88) , 2:jpkm1 ) =    &   ! Strait of Bab el Mandeb 
    252                avt( mi0(161):mi1(161) , mj0( 88):mj1( 88) , 2:jpkm1 ) / 5.e0 
     249               ij0 = 102   ;   ij1 = 102   ;   ii0 = 140   ;   ii1 = 140 
     250               avt( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) , 2:jpkm1 ) =    &   ! Strait of Gibraltar 
     251               avt( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) , 2:jpkm1 ) / 5.e0     
     252               ij0 =  88   ;   ij1 =  88   ;   ii0 = 161   ;   ii1 = 161 
     253               avt( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) , 2:jpkm1 ) =    &   ! Strait of Bab el Mandeb 
     254               avt( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) , 2:jpkm1 ) / 5.e0 
    253255            CASE ( 4  )                         ! ORCA R4 configuration 
    254                avt( mi0( 71):mi1( 71) , mj0( 52):mj1( 52) , 2:jpkm1 ) =    &   ! Strait of Gibraltar 
    255                avt( mi0( 71):mi1( 71) , mj0( 52):mj1( 52) , 2:jpkm1 ) / 5.e0 
     256               ij0 =  52   ;   ij1 =  52   ;   ii0 =  71   ;   ii1 =  71 
     257               avt( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) , 2:jpkm1 ) =    &   ! Strait of Gibraltar 
     258               avt( mi0(ii0):mi1(ii1) , mj0(ij0):mj1(ij1) , 2:jpkm1 ) / 5.e0 
    256259         END SELECT 
    257260      ENDIF 
     
    332335 
    333336      !                                                        ! vertical diffusion 
    334       IF( l_trazdf_exp      )   CALL tra_zdf_exp( kstp )               ! explicit time stepping (time splitting scheme) 
    335       IF( l_trazdf_imp      )   CALL tra_zdf_imp( kstp )               ! implicit time stepping (euler backward) 
    336       IF( l_trazdf_iso      )   CALL tra_zdf_iso( kstp )               ! isopycnal 
     337      IF( l_trazdf_exp      )   CALL tra_zdf_exp     ( kstp )          ! explicit time stepping (time splitting scheme) 
     338      IF( l_trazdf_imp      )   CALL tra_zdf_imp     ( kstp )          ! implicit time stepping (euler backward) 
     339      IF( l_trazdf_iso      )   CALL tra_zdf_iso     ( kstp )          ! isopycnal 
    337340      IF( l_trazdf_iso_vo   )   CALL tra_zdf_iso_vopt( kstp )          ! vector opt. isopycnal 
    338341 
     
    377380 
    378381      !                                                     ! horizontal gradient of Hydrostatic pressure  
    379       IF( l_dyn_hpg     )   CALL dyn_hpg     ( kstp )             ! default case  (k-j-i loop) 
    380       IF( l_dyn_hpg_tsk )   CALL dyn_hpg_atsk( kstp )             ! autatask case (j-k-i loop) 
    381  
    382                             CALL dyn_zad    ( kstp )        ! vertical advection        
     382      IF( lk_dynhpg        )   CALL dyn_hpg     ( kstp )             ! default case  (k-j-i loop) 
     383      IF( lk_dynhpg_tsk    )   CALL dyn_hpg_atsk( kstp )             ! autatask case (j-k-i loop) 
     384 
     385                               CALL dyn_zad    ( kstp )     ! vertical advection        
    383386 
    384387      !                                                     ! vertical diffusion 
  • trunk/NEMO/OPA_SRC/stpctl.F90

    r3 r15  
    5555      INTEGER, DIMENSION(3) ::   ilocu      !  
    5656      INTEGER, DIMENSION(2) ::   ilocs      !  
    57 #if defined key_dynspg_rl 
    58       INTEGER  ::   jni                     ! dummy loop indice 
    59       REAL(wp) ::   zfact                   ! temporary scalar 
    60 #endif 
    6157      !!---------------------------------------------------------------------- 
    6258      !!  OPA 8.5, LODYC-IPSL (2002) 
     
    115111        END DO  
    116112      END DO         
    117 #if defined key_mpp     
    118       CALL mpp_max( zumax ) 
    119 #endif 
     113      IF( lk_mpp )   CALL mpp_max( zumax )   ! max over the global domain 
     114 
    120115      IF( MOD( kt, nwrite ) == 1 ) THEN 
    121116         IF(lwp) WRITE(numout,*) ' ==>> time-step= ',kt,' abs(U) max: ', zumax 
     
    126121         ij = ilocu(2) + njmpp - 1 
    127122         ik = ilocu(3) 
    128 #if defined key_mpp 
    129          CALL mpp_isl( ii ) 
    130          CALL mpp_isl( ij ) 
    131          CALL mpp_isl( ik ) 
    132 #endif 
     123         IF( lk_mpp ) THEN 
     124            CALL mpp_isl( ii ) 
     125            CALL mpp_isl( ij ) 
     126            CALL mpp_isl( ik ) 
     127         ENDIF 
    133128         IF(lwp) THEN 
    134129            WRITE(numout,cform_err) 
     
    155150         END DO 
    156151      END DO 
    157 #if defined key_mpp     
    158       CALL mpp_min( zsmin ) 
    159 #endif 
     152      IF( lk_mpp )   CALL mpp_min( zsmin )   ! min over the global domain 
     153 
    160154      IF( MOD( kt, nwrite ) == 1 ) THEN 
    161155         IF(lwp) WRITE(numout,*) ' ==>> time-step= ',kt,' SSS min:', zsmin 
     
    165159         ii = ilocs(1) + nimpp - 1 
    166160         ij = ilocs(2) + njmpp - 1 
    167 #if defined key_mpp 
    168          CALL mpp_isl( ii ) 
    169          CALL mpp_isl( ij ) 
    170 #endif 
     161         IF( lk_mpp )   CALL mpp_isl( ii ) 
     162         IF( lk_mpp )   CALL mpp_isl( ij ) 
     163 
    171164         IF(lwp) THEN 
    172165            WRITE(numout,cform_err) 
Note: See TracChangeset for help on using the changeset viewer.