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 4229 for branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO – NEMO

Ignore:
Timestamp:
2013-11-18T12:36:11+01:00 (11 years ago)
Author:
cbricaud
Message:

merge UKMO branch into dev_MERCATOR_UKMO_2013

Location:
branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO
Files:
30 edited
4 copied

Legend:

Unmodified
Added
Removed
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/ASM/asminc.F90

    r4070 r4229  
    10161016#endif 
    10171017 
    1018 #if defined key_cice 
     1018#if defined key_cice && defined key_asminc 
    10191019            ! Sea-ice : CICE case. Pass ice increment tendency into CICE 
    10201020            ndaice_da(:,:) = seaice_bkginc(:,:) * zincwgt / rdt 
     
    10271027         ELSE 
    10281028 
    1029 #if defined key_cice 
     1029#if defined key_cice && defined key_asminc 
    10301030            ! Sea-ice : CICE case. Zero ice increment tendency into CICE 
    10311031            ndaice_da(:,:) = 0.0_wp 
     
    10711071#endif 
    10721072  
    1073 #if defined key_cice 
    1074             ! Sea-ice : CICE case. Pass ice increment tendency into CICE - is this correct? 
     1073#if defined key_cice && defined key_asminc 
     1074            ! Sea-ice : CICE case. Pass ice increment tendency into CICE 
    10751075           ndaice_da(:,:) = seaice_bkginc(:,:) / rdt 
    10761076#endif 
     
    10811081         ELSE 
    10821082 
    1083 #if defined key_cice 
     1083#if defined key_cice && defined key_asminc 
    10841084            ! Sea-ice : CICE case. Zero ice increment tendency into CICE  
    10851085            ndaice_da(:,:) = 0.0_wp 
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/C1D/c1d.F90

    r2409 r4229  
    44   !! Ocean domain  :  1D configuration 
    55   !!===================================================================== 
    6    !! History :   2.0  !  2004-09  (C. Ethe)  Original code 
    7    !!             3.0  !  2008-04 (G. Madec)  adaptation to SBC 
     6   !! History :   2.0  !  2004-09 (C. Ethe)     Original code 
     7   !!             3.0  !  2008-04 (G. Madec)    adaptation to SBC 
     8   !!             3.5  !  2013-10 (D. Calvert)  add namelist 
    89   !!---------------------------------------------------------------------- 
     10#if defined key_c1d 
     11   !!---------------------------------------------------------------------- 
     12   !!   'key_c1d'                                   1D column configuration 
     13   !!---------------------------------------------------------------------- 
     14   !!   c1d_init       : read in the C1D namelist 
     15   !!---------------------------------------------------------------------- 
     16   USE in_out_manager   ! I/O manager 
     17   USE par_kind         ! kind parameters 
    918 
    1019   IMPLICIT NONE 
    1120   PRIVATE 
    1221 
    13 #if defined key_c1d 
    14    LOGICAL, PUBLIC, PARAMETER ::   lk_c1d = .TRUE.    !: 1D config. flag activated 
    15 #else 
    16    LOGICAL, PUBLIC, PARAMETER ::   lk_c1d = .FALSE.   !: 1D config. flag de-activated 
    17 #endif 
     22   PUBLIC   c1d_init                                 ! called by nemogcm.F90 
     23 
     24   LOGICAL , PUBLIC, PARAMETER ::  lk_c1d = .TRUE.   ! 1D config. flag 
     25 
     26   REAL(wp), PUBLIC            ::  rn_lat = 50       ! Column latitude 
     27   REAL(wp), PUBLIC            ::  rn_lon = -145     ! Column longitude 
    1828 
    1929   !!---------------------------------------------------------------------- 
     
    2232   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    2333   !!====================================================================== 
     34CONTAINS 
     35 
     36   SUBROUTINE c1d_init 
     37      !!---------------------------------------------------------------------- 
     38      !!                  ***  ROUTINE c1d_init  *** 
     39      !!  
     40      !! ** Purpose :   Initialization of C1D options 
     41      !! 
     42      !! ** Method  :   Read namelist namc1d  
     43      !!---------------------------------------------------------------------- 
     44      NAMELIST/namc1d/ rn_lat, rn_lon 
     45      !!---------------------------------------------------------------------- 
     46      ! 
     47      REWIND ( numnam )               ! Read C1D options from namelist 
     48      READ   ( numnam, namc1d ) 
     49      ! 
     50      IF(lwp) THEN                    ! Control print 
     51         WRITE(numout,*) 
     52         WRITE(numout,*) 'c1d_init : Initialize 1D model configuration options' 
     53         WRITE(numout,*) '~~~~~~~~' 
     54         WRITE(numout,*) '   Namelist namc1d : set options for the C1D model' 
     55         WRITE(numout,*) '      column latitude                 rn_lat = ', rn_lat 
     56         WRITE(numout,*) '      column longitude                rn_lon = ', rn_lon 
     57      ENDIF 
     58      ! 
     59      ! 
     60   END SUBROUTINE c1d_init 
     61 
     62#else 
     63   !!---------------------------------------------------------------------- 
     64   !!   Dummy module :                           No use of 1D configuration 
     65   !!---------------------------------------------------------------------- 
     66   LOGICAL, PUBLIC, PARAMETER ::   lk_c1d = .FALSE.   !: 1D config. flag de-activated 
     67   REAL                       ::   rn_lat, rn_lon 
     68CONTAINS 
     69 
     70   SUBROUTINE c1d_init               ! Dummy routine 
     71   END SUBROUTINE c1d_init 
     72 
     73#endif 
     74 
     75   !!====================================================================== 
    2476END MODULE c1d 
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/C1D/step_c1d.F90

    r3971 r4229  
    1313   !!   stp_c1d        : NEMO system time-stepping in c1d case 
    1414   !!---------------------------------------------------------------------- 
    15    USE step_oce         ! time stepping definition modules  
     15   USE step_oce        ! time stepping definition modules  
    1616#if defined key_top 
    17    USE trcstp           ! passive tracer time-stepping      (trc_stp routine) 
     17   USE trcstp          ! passive tracer time-stepping      (trc_stp routine) 
    1818#endif 
    1919   USE dyncor_c1d      ! Coriolis term (c1d case)         (dyn_cor_1d     ) 
    2020   USE dynnxt_c1d      ! time-stepping                    (dyn_nxt routine) 
     21   USE dyndmp          ! U & V momentum damping           (dyn_dmp routine) 
    2122   USE restart         ! restart  
    2223 
     
    124125                             CALL tra_sbc    ( kstp )        ! surface boundary condition 
    125126      IF( ln_traqsr      )   CALL tra_qsr    ( kstp )        ! penetrative solar radiation qsr 
     127      IF( ln_tradmp      )   CALL tra_dmp    ( kstp )        ! internal damping trends- tracers 
    126128      IF( lk_zdfkpp      )   CALL tra_kpp    ( kstp )        ! KPP non-local tracer fluxes 
    127129                             CALL tra_zdf    ( kstp )        ! vertical mixing 
     
    136138                               va(:,:,:) = 0.e0 
    137139 
     140      IF( ln_dyndmp      )     CALL dyn_dmp    ( kstp )       ! internal damping trends- momentum 
    138141                               CALL dyn_cor_c1d( kstp )       ! vorticity term including Coriolis 
    139142                               CALL dyn_zdf    ( kstp )       ! vertical diffusion 
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/DOM/domcfg.F90

    r3294 r4229  
    1616   USE lib_mpp         ! distributed memory computing library 
    1717   USE timing          ! Timing 
     18   USE c1d             ! 1D configuration 
     19   USE domc1d          ! 1D configuration: column location 
    1820 
    1921   IMPLICIT NONE 
     
    8082      !!---------------------------------------------------------------------- 
    8183 
     84      !                              ! recalculate jpizoom/jpjzoom given lat/lon 
     85      IF( lk_c1d )  CALL dom_c1d( rn_lat, rn_lon ) 
     86      ! 
    8287      !                        ! ============== ! 
    8388      !                        !  Local domain  !  
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/DOM/domzgr.F90

    r4228 r4229  
    11731173      !                                        ! ============================= 
    11741174      ! use r-value to create hybrid coordinates 
     1175      zenv(:,:) = bathy(:,:) 
     1176      ! 
     1177      ! set first land point adjacent to a wet cell to sbot_min as this needs to be included in smoothing 
    11751178      DO jj = 1, jpj 
    11761179         DO ji = 1, jpi 
    1177             zenv(ji,jj) = MAX( bathy(ji,jj), rn_sbot_min ) 
    1178          END DO 
    1179       END DO 
     1180           IF( bathy(ji,jj) == 0._wp ) THEN 
     1181             iip1 = MIN( ji+1, jpi ) 
     1182             ijp1 = MIN( jj+1, jpj ) 
     1183             iim1 = MAX( ji-1, 1 ) 
     1184             ijm1 = MAX( jj-1, 1 ) 
     1185             IF( (bathy(iip1,jj) + bathy(iim1,jj) + bathy(ji,ijp1) + bathy(ji,ijm1) +              & 
     1186        &         bathy(iip1,ijp1) + bathy(iim1,ijm1) + bathy(iip1,ijp1) + bathy(iim1,ijm1)) > 0._wp ) THEN 
     1187               zenv(ji,jj) = rn_sbot_min 
     1188             ENDIF 
     1189           ENDIF 
     1190         END DO 
     1191      END DO 
     1192      ! apply lateral boundary condition   CAUTION: keep the value when the lbc field is zero 
     1193      CALL lbc_lnk( zenv, 'T', 1._wp, 'no0' ) 
    11801194      !  
    1181       ! Smooth the bathymetry (if required) 
     1195      ! smooth the bathymetry (if required) 
    11821196      scosrf(:,:) = 0._wp             ! ocean surface depth (here zero: no under ice-shelf sea) 
    11831197      scobot(:,:) = bathy(:,:)        ! ocean bottom  depth 
     
    11851199      jl = 0 
    11861200      zrmax = 1._wp 
    1187       !                                                     ! ================ ! 
    1188       DO WHILE( jl <= 10000 .AND. zrmax > rn_rmax )         !  Iterative loop  ! 
    1189          !                                                  ! ================ ! 
     1201      !    
     1202      !      
     1203      ! set scaling factor used in reducing vertical gradients 
     1204      zrfact = ( 1._wp - rn_rmax ) / ( 1._wp + rn_rmax ) 
     1205      ! 
     1206      ! initialise temporary evelope depth arrays 
     1207      ztmpi1(:,:) = zenv(:,:) 
     1208      ztmpi2(:,:) = zenv(:,:) 
     1209      ztmpj1(:,:) = zenv(:,:) 
     1210      ztmpj2(:,:) = zenv(:,:) 
     1211      ! 
     1212      ! initialise temporary r-value arrays 
     1213      zri(:,:) = 1._wp 
     1214      zrj(:,:) = 1._wp 
     1215      !                                                            ! ================ ! 
     1216      DO WHILE( jl <= 10000 .AND. ( zrmax - rn_rmax ) > 1.e-8_wp ) !  Iterative loop  ! 
     1217         !                                                         ! ================ ! 
    11901218         jl = jl + 1 
    11911219         zrmax = 0._wp 
    1192          zmsk(:,:) = 0._wp 
     1220         ! we set zrmax from previous r-values (zri and zrj) first 
     1221         ! if set after current r-value calculation (as previously) 
     1222         ! we could exit DO WHILE prematurely before checking r-value 
     1223         ! of current zenv 
     1224         DO jj = 1, nlcj 
     1225            DO ji = 1, nlci 
     1226               zrmax = MAX( zrmax, ABS(zri(ji,jj)), ABS(zrj(ji,jj)) ) 
     1227            END DO 
     1228         END DO 
     1229         zri(:,:) = 0._wp 
     1230         zrj(:,:) = 0._wp 
    11931231         DO jj = 1, nlcj 
    11941232            DO ji = 1, nlci 
    11951233               iip1 = MIN( ji+1, nlci )      ! force zri = 0 on last line (ji=ncli+1 to jpi) 
    11961234               ijp1 = MIN( jj+1, nlcj )      ! force zrj = 0 on last raw  (jj=nclj+1 to jpj) 
    1197                zri(ji,jj) = ABS( zenv(iip1,jj  ) - zenv(ji,jj) ) / ( zenv(iip1,jj  ) + zenv(ji,jj) ) 
    1198                zrj(ji,jj) = ABS( zenv(ji  ,ijp1) - zenv(ji,jj) ) / ( zenv(ji  ,ijp1) + zenv(ji,jj) ) 
    1199                zrmax = MAX( zrmax, zri(ji,jj), zrj(ji,jj) ) 
    1200                IF( zri(ji,jj) > rn_rmax )   zmsk(ji  ,jj  ) = 1._wp 
    1201                IF( zri(ji,jj) > rn_rmax )   zmsk(iip1,jj  ) = 1._wp 
    1202                IF( zrj(ji,jj) > rn_rmax )   zmsk(ji  ,jj  ) = 1._wp 
    1203                IF( zrj(ji,jj) > rn_rmax )   zmsk(ji  ,ijp1) = 1._wp 
     1235               IF( (zenv(ji,jj) > 0._wp) .AND. (zenv(iip1,jj) > 0._wp)) THEN 
     1236                  zri(ji,jj) = ( zenv(iip1,jj  ) - zenv(ji,jj) ) / ( zenv(iip1,jj  ) + zenv(ji,jj) ) 
     1237               END IF 
     1238               IF( (zenv(ji,jj) > 0._wp) .AND. (zenv(ji,ijp1) > 0._wp)) THEN 
     1239                  zrj(ji,jj) = ( zenv(ji  ,ijp1) - zenv(ji,jj) ) / ( zenv(ji  ,ijp1) + zenv(ji,jj) ) 
     1240               END IF 
     1241               IF( zri(ji,jj) >  rn_rmax )   ztmpi1(ji  ,jj  ) = zenv(iip1,jj  ) * zrfact 
     1242               IF( zri(ji,jj) < -rn_rmax )   ztmpi2(iip1,jj  ) = zenv(ji  ,jj  ) * zrfact 
     1243               IF( zrj(ji,jj) >  rn_rmax )   ztmpj1(ji  ,jj  ) = zenv(ji  ,ijp1) * zrfact 
     1244               IF( zrj(ji,jj) < -rn_rmax )   ztmpj2(ji  ,ijp1) = zenv(ji  ,jj  ) * zrfact 
    12041245            END DO 
    12051246         END DO 
    12061247         IF( lk_mpp )   CALL mpp_max( zrmax )   ! max over the global domain 
    1207          ! lateral boundary condition on zmsk: keep 1 along closed boundary (use of MAX) 
    1208          ztmp(:,:) = zmsk(:,:)   ;   CALL lbc_lnk( zmsk, 'T', 1._wp ) 
    1209          DO jj = 1, nlcj 
    1210             DO ji = 1, nlci 
    1211                 zmsk(ji,jj) = MAX( zmsk(ji,jj), ztmp(ji,jj) ) 
    1212             END DO 
    1213          END DO 
    12141248         ! 
    1215          IF(lwp)WRITE(numout,*) 'zgr_sco :   iter= ',jl, ' rmax= ', zrmax, ' nb of pt= ', INT( SUM(zmsk(:,:) ) ) 
     1249         IF(lwp)WRITE(numout,*) 'zgr_sco :   iter= ',jl, ' rmax= ', zrmax 
    12161250         ! 
    12171251         DO jj = 1, nlcj 
    12181252            DO ji = 1, nlci 
    1219                iip1 = MIN( ji+1, nlci )     ! last  line (ji=nlci) 
    1220                ijp1 = MIN( jj+1, nlcj )     ! last  raw  (jj=nlcj) 
    1221                iim1 = MAX( ji-1,  1  )      ! first line (ji=nlci) 
    1222                ijm1 = MAX( jj-1,  1  )      ! first raw  (jj=nlcj) 
    1223                IF( zmsk(ji,jj) == 1._wp ) THEN 
    1224                   ztmp(ji,jj) =   (                                                                                   & 
    1225              &      zenv(iim1,ijp1)*zmsk(iim1,ijp1) + zenv(ji,ijp1)*zmsk(ji,ijp1) + zenv(iip1,ijp1)*zmsk(iip1,ijp1)   & 
    1226              &    + zenv(iim1,jj  )*zmsk(iim1,jj  ) + zenv(ji,jj  )*    2._wp     + zenv(iip1,jj  )*zmsk(iip1,jj  )   & 
    1227              &    + zenv(iim1,ijm1)*zmsk(iim1,ijm1) + zenv(ji,ijm1)*zmsk(ji,ijm1) + zenv(iip1,ijm1)*zmsk(iip1,ijm1)   & 
    1228              &                    ) / (                                                                               & 
    1229              &                      zmsk(iim1,ijp1) +               zmsk(ji,ijp1) +                 zmsk(iip1,ijp1)   & 
    1230              &    +                 zmsk(iim1,jj  ) +                   2._wp     +                 zmsk(iip1,jj  )   & 
    1231              &    +                 zmsk(iim1,ijm1) +               zmsk(ji,ijm1) +                 zmsk(iip1,ijm1)   & 
    1232              &                        ) 
    1233                ENDIF 
    1234             END DO 
    1235          END DO 
    1236          ! 
    1237          DO jj = 1, nlcj 
    1238             DO ji = 1, nlci 
    1239                IF( zmsk(ji,jj) == 1._wp )   zenv(ji,jj) = MAX( ztmp(ji,jj), bathy(ji,jj) ) 
    1240             END DO 
    1241          END DO 
    1242          ! 
    1243          ! Apply lateral boundary condition   CAUTION: keep the value when the lbc field is zero 
    1244          ztmp(:,:) = zenv(:,:)   ;   CALL lbc_lnk( zenv, 'T', 1._wp ) 
    1245          DO jj = 1, nlcj 
    1246             DO ji = 1, nlci 
    1247                IF( zenv(ji,jj) == 0._wp )   zenv(ji,jj) = ztmp(ji,jj) 
    1248             END DO 
    1249          END DO 
     1253               zenv(ji,jj) = MAX(zenv(ji,jj), ztmpi1(ji,jj), ztmpi2(ji,jj), ztmpj1(ji,jj), ztmpj2(ji,jj) ) 
     1254            END DO 
     1255         END DO 
     1256         ! apply lateral boundary condition   CAUTION: keep the value when the lbc field is zero 
     1257         CALL lbc_lnk( zenv, 'T', 1._wp, 'no0' ) 
    12501258         !                                                  ! ================ ! 
    12511259      END DO                                                !     End loop     ! 
    12521260      !                                                     ! ================ ! 
    1253       ! 
    1254       ! Fill ghost rows with appropriate values to avoid undefined e3 values with some mpp decompositions 
    1255       DO ji = nlci+1, jpi  
    1256          zenv(ji,1:nlcj) = zenv(nlci,1:nlcj) 
    1257       END DO 
    1258       ! 
    1259       DO jj = nlcj+1, jpj 
    1260          zenv(:,jj) = zenv(:,nlcj) 
     1261      DO jj = 1, jpj 
     1262         DO ji = 1, jpi 
     1263            zenv(ji,jj) = MAX( zenv(ji,jj), rn_sbot_min ) ! set all points to avoid undefined scale value warnings 
     1264         END DO 
    12611265      END DO 
    12621266      ! 
     
    15361540      END DO 
    15371541      ! 
    1538       CALL wrk_dealloc( jpi, jpj,      zenv, ztmp, zmsk, zri, zrj, zhbat                           ) 
     1542      CALL wrk_dealloc( jpi, jpj,      zenv, ztmpi1, ztmpi2, ztmpj1, ztmpj2, zri, zrj, zhbat                           )      ! 
    15391543      ! 
    15401544      IF( nn_timing == 1 )  CALL timing_stop('zgr_sco') 
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/DOM/istate.F90

    r4228 r4229  
    2626   USE oce             ! ocean dynamics and active tracers  
    2727   USE dom_oce         ! ocean space and time domain  
     28   USE c1d             ! 1D vertical configuration 
    2829   USE daymod          ! calendar 
    2930   USE eosbn2          ! eq. of state, Brunt Vaisala frequency (eos     routine) 
     
    3233   USE phycst          ! physical constants 
    3334   USE dtatsd          ! data temperature and salinity   (dta_tsd routine) 
     35   USE dtauvd          ! data: U & V current             (dta_uvd routine) 
    3436   USE in_out_manager  ! I/O manager 
    3537   USE iom             ! I/O library 
     
    7072      ! - ML - needed for initialization of e3t_b 
    7173      INTEGER  ::  jk     ! dummy loop indice 
     74      REAL(wp), POINTER, DIMENSION(:,:,:,:)  ::  zuvd    ! U & V data workspace 
    7275      !!---------------------------------------------------------------------- 
    7376      ! 
     
    8083 
    8184      CALL dta_tsd_init                       ! Initialisation of T & S input data 
     85      IF( lk_c1d ) CALL dta_uvd_init          ! Initialization of U & V input data 
    8286 
    8387      rhd  (:,:,:  ) = 0.e0 
     
    111115         ELSEIF( cp_cfg == 'gyre' ) THEN          
    112116            CALL istate_gyre                     ! GYRE  configuration : start from pre-defined T-S fields 
    113          ELSEIF( ln_tsd_init      ) THEN         ! Initial T-S fields read in files 
    114             CALL dta_tsd( nit000, tsb )                  ! read 3D T and S data at nit000 
    115             tsn(:,:,:,:) = tsb(:,:,:,:) 
    116             ! 
    117          ELSE                                    ! Initial T-S fields defined analytically 
    118             CALL istate_t_s 
     117         ELSE                                    ! Initial T-S, U-V fields read in files 
     118            IF ( ln_tsd_init ) THEN              ! read 3D T and S data at nit000 
     119               CALL dta_tsd( nit000, tsb )   
     120               tsn(:,:,:,:) = tsb(:,:,:,:) 
     121               ! 
     122            ELSE                                 ! Initial T-S fields defined analytically 
     123               CALL istate_t_s 
     124            ENDIF 
     125            IF ( ln_uvd_init .AND. lk_c1d ) THEN ! read 3D U and V data at nit000 
     126               CALL wrk_alloc( jpi, jpj, jpk, 2, zuvd ) 
     127               CALL dta_uvd( nit000, zuvd ) 
     128               ub(:,:,:) = zuvd(:,:,:,1) ;  un(:,:,:) = ub(:,:,:) 
     129               vb(:,:,:) = zuvd(:,:,:,2) ;  vn(:,:,:) = vb(:,:,:) 
     130               CALL wrk_dealloc( jpi, jpj, jpk, 2, zuvd ) 
     131            ENDIF 
    119132         ENDIF 
    120133         ! 
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg.F90

    r3625 r4229  
    1414   USE oce            ! ocean dynamics and tracers variables 
    1515   USE dom_oce        ! ocean space and time domain variables 
     16   USE c1d            ! 1D vertical configuration 
    1617   USE phycst         ! physical constants 
    1718   USE sbc_oce        ! surface boundary condition: ocean 
     
    220221      IF(lk_dynspg_flt)   ioptio = ioptio + 1 
    221222      ! 
    222       IF( ( ioptio > 1 .AND. .NOT. lk_esopa ) .OR. ioptio == 0 )   & 
     223      IF( ( ioptio > 1 .AND. .NOT. lk_esopa ) .OR. ( ioptio == 0 .AND. .NOT. lk_c1d ) )   & 
    223224           &   CALL ctl_stop( ' Choose only one surface pressure gradient scheme with a key cpp' ) 
    224225      ! 
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/IOM/iom.F90

    r3983 r4229  
    463463   !!                   INTERFACE iom_get 
    464464   !!---------------------------------------------------------------------- 
    465    SUBROUTINE iom_g0d( kiomid, cdvar, pvar ) 
     465   SUBROUTINE iom_g0d( kiomid, cdvar, pvar, ktime ) 
    466466      INTEGER         , INTENT(in   )                 ::   kiomid    ! Identifier of the file 
    467467      CHARACTER(len=*), INTENT(in   )                 ::   cdvar     ! Name of the variable 
    468468      REAL(wp)        , INTENT(  out)                 ::   pvar      ! read field 
    469       ! 
    470       INTEGER               :: idvar   ! variable id 
     469      INTEGER         , INTENT(in   ),     OPTIONAL   ::   ktime     ! record number 
     470      ! 
     471      INTEGER                                         ::   idvar     ! variable id 
     472      INTEGER                                         ::   idmspc    ! number of spatial dimensions 
     473      INTEGER         , DIMENSION(1)                  ::   itime     ! record number 
     474      CHARACTER(LEN=100)                              ::   clinfo    ! info character 
     475      CHARACTER(LEN=100)                              ::   clname    ! file name 
     476      CHARACTER(LEN=1)                                ::   cldmspc   ! 
     477      ! 
     478      itime = 1 
     479      IF( PRESENT(ktime) ) itime = ktime 
     480      ! 
     481      clname = iom_file(kiomid)%name 
     482      clinfo = '          iom_g0d, file: '//trim(clname)//', var: '//trim(cdvar) 
    471483      ! 
    472484      IF( kiomid > 0 ) THEN 
    473485         idvar = iom_varid( kiomid, cdvar ) 
    474486         IF( iom_file(kiomid)%nfid > 0 .AND. idvar > 0 ) THEN 
     487            idmspc = iom_file ( kiomid )%ndims( idvar ) 
     488            IF( iom_file(kiomid)%luld(idvar) )  idmspc = idmspc - 1 
     489            WRITE(cldmspc , fmt='(i1)') idmspc 
     490            IF( idmspc > 0 )  CALL ctl_stop( TRIM(clinfo), 'When reading to a 0D array, we do not accept data', & 
     491                                 &                         'with 1 or more spatial dimensions: '//cldmspc//' were found.' , & 
     492                                 &                         'Use ncwa -a to suppress the unnecessary dimensions' ) 
    475493            SELECT CASE (iom_file(kiomid)%iolib) 
    476             CASE (jpioipsl )   ;   CALL iom_ioipsl_get(  kiomid, idvar, pvar ) 
    477             CASE (jpnf90   )   ;   CALL iom_nf90_get(    kiomid, idvar, pvar ) 
     494            CASE (jpioipsl )   ;   CALL iom_ioipsl_get(  kiomid, idvar, pvar, itime ) 
     495            CASE (jpnf90   )   ;   CALL iom_nf90_get(    kiomid, idvar, pvar, itime ) 
    478496            CASE (jprstdimg)   ;   CALL iom_rstdimg_get( kiomid, idvar, pvar ) 
    479497            CASE DEFAULT     
     
    640658               ELSE 
    641659                  CALL ctl_stop( TRIM(clinfo), 'To keep iom lisibility, when reading a '//clrankpv//'D array,'         ,   & 
    642                      &                         'we do not accept data with more than '//cldmspc//' spatial dimension',   & 
     660                     &                         'we do not accept data with '//cldmspc//' spatial dimensions',   & 
    643661                     &                         'Use ncwa -a to suppress the unnecessary dimensions' ) 
    644662               ENDIF 
     
    752770 
    753771         IF( istop == nstop ) THEN   ! no additional errors until this point... 
    754             IF(lwp) WRITE(numout,"(10x,' read ',a,' (rec: ',i4,') in ',a,' ok')") TRIM(cdvar), itime, TRIM(iom_file(kiomid)%name) 
     772            IF(lwp) WRITE(numout,"(10x,' read ',a,' (rec: ',i6,') in ',a,' ok')") TRIM(cdvar), itime, TRIM(iom_file(kiomid)%name) 
    755773           
    756774            !--- overlap areas and extra hallows (mpp) 
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/IOM/iom_ioipsl.F90

    r2715 r4229  
    170170            iom_file(kiomid)%cn_var(kiv) = TRIM(cdvar) 
    171171            iom_file(kiomid)%ndims(kiv)  = i_nvd 
     172            iom_file(kiomid)%dimsz(:,kiv) = 0   ! reset dimsz in case previously used 
    172173            CALL flioinqv( ioipslid, cdvar, ll_fnd,   & 
    173174                  &           len_dims = iom_file(kiomid)%dimsz(1:i_nvd,kiv), &   ! dimensions size 
     
    210211 
    211212 
    212    SUBROUTINE iom_ioipsl_g0d( kiomid, kvid, pvar ) 
     213   SUBROUTINE iom_ioipsl_g0d( kiomid, kvid, pvar, kstart ) 
    213214      !!----------------------------------------------------------------------- 
    214215      !!                  ***  ROUTINE  iom_ioipsl_g0d  *** 
     
    216217      !! ** Purpose : read a scalar with IOIPSL (only fliocom module) 
    217218      !!----------------------------------------------------------------------- 
    218       INTEGER , INTENT(in   ) ::   kiomid    ! Identifier of the file 
    219       INTEGER , INTENT(in   ) ::   kvid      ! variable id 
    220       REAL(wp), INTENT(  out) ::   pvar      ! read field 
    221       ! 
    222       CALL fliogetv( iom_file(kiomid)%nfid, TRIM(iom_file(kiomid)%cn_var(kvid)), pvar ) 
     219      INTEGER ,               INTENT(in   )            ::   kiomid    ! Identifier of the file 
     220      INTEGER ,               INTENT(in   )            ::   kvid      ! variable id 
     221      REAL(wp),               INTENT(  out)            ::   pvar      ! read field 
     222      INTEGER , DIMENSION(1), INTENT(in   ), OPTIONAL  ::   kstart    ! start position of the reading in each axis 
     223      ! 
     224      CALL fliogetv( iom_file(kiomid)%nfid, TRIM(iom_file(kiomid)%cn_var(kvid)), pvar, kstart ) 
    223225      !  
    224226   END SUBROUTINE iom_ioipsl_g0d 
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/IOM/iom_nf90.F90

    r2715 r4229  
    216216         CALL iom_nf90_check(NF90_Inquire_Variable(if90id, ivarid, dimids = idimid(1:i_nvd)), clinfo)   ! dimensions ids 
    217217         iom_file(kiomid)%luld(kiv) = .FALSE.   ! default value 
     218         iom_file(kiomid)%dimsz(:,kiv) = 0   ! reset dimsz in case previously used 
    218219         DO ji = 1, i_nvd                       ! dimensions size 
    219220            CALL iom_nf90_check(NF90_Inquire_Dimension(if90id, idimid(ji), len = iom_file(kiomid)%dimsz(ji,kiv)), clinfo)    
     
    249250 
    250251 
    251    SUBROUTINE iom_nf90_g0d( kiomid, kvid, pvar ) 
     252   SUBROUTINE iom_nf90_g0d( kiomid, kvid, pvar, kstart ) 
    252253      !!----------------------------------------------------------------------- 
    253254      !!                  ***  ROUTINE  iom_nf90_g0d  *** 
     
    255256      !! ** Purpose : read a scalar with NF90 
    256257      !!----------------------------------------------------------------------- 
    257       INTEGER , INTENT(in   ) ::   kiomid   ! Identifier of the file 
    258       INTEGER , INTENT(in   ) ::   kvid     ! variable id 
    259       REAL(wp), INTENT(  out) ::   pvar     ! read field 
     258      INTEGER ,               INTENT(in   )            ::   kiomid   ! Identifier of the file 
     259      INTEGER ,               INTENT(in   )            ::   kvid     ! variable id 
     260      REAL(wp),               INTENT(  out)            ::   pvar     ! read field 
     261      INTEGER , DIMENSION(1), INTENT(in   ), OPTIONAL  ::   kstart   ! start position of the reading in each axis 
    260262      ! 
    261263      CHARACTER(LEN=100)      ::   clinfo   ! info character 
    262264      !--------------------------------------------------------------------- 
    263265      clinfo = 'iom_nf90_g0d , file: '//TRIM(iom_file(kiomid)%name)//', var: '//TRIM(iom_file(kiomid)%cn_var(kvid)) 
    264       CALL iom_nf90_check(NF90_GET_VAR(iom_file(kiomid)%nfid, iom_file(kiomid)%nvid(kvid), pvar), clinfo ) 
     266      CALL iom_nf90_check(NF90_GET_VAR(iom_file(kiomid)%nfid, iom_file(kiomid)%nvid(kvid), pvar, start = kstart), clinfo ) 
    265267      !  
    266268   END SUBROUTINE iom_nf90_g0d 
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/OBS/diaobs.F90

    r3651 r4229  
    2121   USE par_oce 
    2222   USE dom_oce                  ! Ocean space and time domain variables 
     23   USE obs_fbm, ONLY: ln_cl4    ! Class 4 diagnostic switch 
    2324   USE obs_read_prof            ! Reading and allocation of observations (Coriolis) 
    2425   USE obs_read_sla             ! Reading and allocation of SLA observations   
     
    4849   PUBLIC dia_obs_init, &  ! Initialize and read observations 
    4950      &   dia_obs,      &  ! Compute model equivalent to observations 
    50       &   dia_obs_wri      ! Write model equivalent to observations 
     51      &   dia_obs_wri,  &  ! Write model equivalent to observations 
     52      &   dia_obs_dealloc  ! Deallocate dia_obs data 
    5153 
    5254   !! * Shared Module variables 
     
    8082   LOGICAL, PUBLIC :: ln_ssh         !: Logical switch for sea surface height 
    8183   LOGICAL, PUBLIC :: ln_sss         !: Logical switch for sea surface salinity 
     84   LOGICAL, PUBLIC :: ln_sstnight    !: Logical switch for night mean SST observations 
    8285   LOGICAL, PUBLIC :: ln_nea         !: Remove observations near land 
    8386   LOGICAL, PUBLIC :: ln_altbias     !: Logical switch for altimeter bias   
     
    167170         &            nmsshc, mdtcorr, mdtcutoff,                     & 
    168171         &            ln_reysst, ln_ghrsst, reysstname, reysstfmt,    & 
     172         &            ln_sstnight,                                    & 
    169173         &            ln_grid_search_lookup,                          & 
    170174         &            grid_search_file, grid_search_res,              & 
     
    176180         &            ln_velhradcp, velhradcpfiles,                   & 
    177181         &            ln_velfb, velfbfiles, ln_velfb_av,              & 
    178          &            ln_profb_enatim, ln_ignmis 
     182         &            ln_profb_enatim, ln_ignmis, ln_cl4 
    179183 
    180184      INTEGER :: jprofset 
     
    226230      ln_velhradcp = .FALSE. 
    227231      ln_velfb = .FALSE. 
     232      ln_sstnight = .FALSE. 
    228233      ln_nea = .FALSE. 
    229234      ln_grid_search_lookup = .FALSE. 
    230235      ln_grid_global = .FALSE. 
    231236      ln_s_at_t = .TRUE. 
     237      ln_cl4 = .FALSE. 
    232238      grid_search_file = 'xypos' 
    233239      bias_file='bias.nc' 
     
    357363         WRITE(numout,*) '             Logical switch for GHRSST observations          ln_ghrsst = ', ln_ghrsst 
    358364         WRITE(numout,*) '             Logical switch for feedback SST data             ln_sstfb = ', ln_sstfb 
     365         WRITE(numout,*) '             Logical switch for night-time SST obs         ln_sstnight = ', ln_sstnight 
    359366         WRITE(numout,*) '             Logical switch for SSS observations                ln_sss = ', ln_sss 
    360367         WRITE(numout,*) '             Logical switch for Sea Ice observations         ln_seaice = ', ln_seaice 
     
    750757            nsstsets = nsstsets + 1 
    751758 
    752             ld_sstnight(nsstsets) = .TRUE. 
     759            ld_sstnight(nsstsets) = ln_sstnight 
    753760 
    754761            CALL obs_rea_sst_rey( reysstname, reysstfmt, sstdata(nsstsets), & 
     
    764771            nsstsets = nsstsets + 1 
    765772 
    766             ld_sstnight(nsstsets) = .TRUE. 
     773            ld_sstnight(nsstsets) = ln_sstnight 
    767774           
    768775            CALL obs_rea_sst( 1, sstdata(nsstsets), jnumsst, & 
     
    783790               nsstsets = nsstsets + 1 
    784791 
    785                ld_sstnight(nsstsets) = .TRUE. 
     792               ld_sstnight(nsstsets) = ln_sstnight 
    786793             
    787794               CALL obs_rea_sst( 0, sstdata(nsstsets), 1, & 
     
    14141421   END SUBROUTINE dia_obs_wri 
    14151422 
     1423   SUBROUTINE dia_obs_dealloc 
     1424      IMPLICIT NONE 
     1425      !!---------------------------------------------------------------------- 
     1426      !!                    *** ROUTINE dia_obs_dealloc *** 
     1427      !! 
     1428      !!  ** Purpose : To deallocate data to enable the obs_oper online loop. 
     1429      !!               Specifically: dia_obs_init --> dia_obs --> dia_obs_wri 
     1430      !! 
     1431      !!  ** Method : Clean up various arrays left behind by the obs_oper. 
     1432      !! 
     1433      !!  ** Action : 
     1434      !! 
     1435      !!---------------------------------------------------------------------- 
     1436      !! obs_grid deallocation 
     1437      CALL obs_grid_deallocate 
     1438 
     1439      !! diaobs deallocation 
     1440      IF ( nprofsets > 0 ) THEN 
     1441          DEALLOCATE(ld_enact, & 
     1442                  &  profdata, & 
     1443                  &  prodatqc) 
     1444      END IF 
     1445      IF ( ln_sla ) THEN 
     1446          DEALLOCATE(sladata, & 
     1447                  &  sladatqc) 
     1448      END IF 
     1449      IF ( ln_seaice ) THEN 
     1450          DEALLOCATE(sladata, & 
     1451                  &  sladatqc) 
     1452      END IF 
     1453      IF ( ln_sst ) THEN 
     1454          DEALLOCATE(sstdata, & 
     1455                  &  sstdatqc) 
     1456      END IF 
     1457      IF ( ln_vel3d ) THEN 
     1458          DEALLOCATE(ld_velav, & 
     1459                  &  velodata, & 
     1460                  &  veldatqc) 
     1461      END IF 
     1462   END SUBROUTINE dia_obs_dealloc 
     1463 
    14161464   SUBROUTINE ini_date( ddobsini ) 
    14171465      !!---------------------------------------------------------------------- 
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/OBS/mpp_map.F90

    r2363 r4229  
    5252      !!---------------------------------------------------------------------- 
    5353 
    54       ALLOCATE( & 
    55          & mppmap(jpiglo,jpjglo) & 
    56          & ) 
    57  
     54      IF (.NOT. ALLOCATED(mppmap)) THEN 
     55         ALLOCATE( & 
     56            & mppmap(jpiglo,jpjglo) & 
     57            & ) 
     58      ENDIF 
    5859      ! Initialize local imppmap 
    5960 
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/OBS/obs_fbm.F90

    r2287 r4229  
    4545   INTEGER, PARAMETER    :: fbimdi = -99999   !: Integers 
    4646   REAL(fbsp), PARAMETER :: fbrmdi =  99999   !: Reals 
    47     
     47 
     48   ! Output stream choice 
     49   LOGICAL               :: ln_cl4 = .FALSE.  !: Logical switch for 
     50                                              !: class 4 file outputs 
     51  
    4852   ! Main data structure for observation feedback data. 
    4953 
     
    10261030 
    10271031   SUBROUTINE write_obfbdata( cdfilename, fbdata ) 
     1032      !!---------------------------------------------------------------------- 
     1033      !!                    ***  ROUTINE write_obfbdata  *** 
     1034      !! 
     1035      !! ** Purpose :   Write an obfbdata structure into a netCDF file. 
     1036      !! 
     1037      !! ** Method  :   Decides which output wrapper to use.  
     1038      !! 
     1039      !! ** Action  :  
     1040      !! 
     1041      !!---------------------------------------------------------------------- 
     1042      !! * Arguments 
     1043      CHARACTER(len=*) :: cdfilename ! Output filename 
     1044      TYPE(obfbdata)   :: fbdata     ! obsfbdata structure 
     1045#if defined key_offobsoper 
     1046      IF (ln_cl4) THEN 
     1047          ! Class 4 file output stream 
     1048          CALL write_obfbdata_cl( cdfilename, fbdata ) 
     1049      ELSE 
     1050#endif 
     1051          ! Standard feedback file output stream 
     1052          CALL write_obfbdata_fb( cdfilename, fbdata ) 
     1053#if defined key_offobsoper 
     1054      ENDIF 
     1055#endif 
     1056   END SUBROUTINE write_obfbdata 
     1057 
     1058   SUBROUTINE write_obfbdata_fb( cdfilename, fbdata ) 
    10281059      !!---------------------------------------------------------------------- 
    10291060      !!                    ***  ROUTINE write_obfbdata  *** 
     
    15241555 
    15251556       
    1526    END SUBROUTINE write_obfbdata 
     1557   END SUBROUTINE write_obfbdata_fb 
     1558 
     1559#if defined key_offobsoper 
     1560   SUBROUTINE write_obfbdata_cl(cdfilename, fbdata) 
     1561      !!---------------------------------------------------------------------- 
     1562      !!                    ***  ROUTINE write_obfbdata_cl  *** 
     1563      !! 
     1564      !! ** Purpose : Write an obfbdata structure into a class 4 file. 
     1565      !! 
     1566      !! ** Method  : 1. Allocate memory needed by ooo_write 
     1567      !!              2. Map obfbdata into allocated memory 
     1568      !!              3. Pass mapped data to ooo_write 
     1569      !!              4. Deallocate memory 
     1570      !!---------------------------------------------------------------------- 
     1571      USE dom_oce, ONLY: narea 
     1572      USE ooo_write 
     1573      USE ooo_data 
     1574      !! * Arguments 
     1575      CHARACTER(len=*) :: cdfilename ! Feedback filename 
     1576      TYPE(obfbdata)   :: fbdata     ! obsfbdata structure 
     1577      !! * Local variables 
     1578      CHARACTER(len=17), PARAMETER :: cpname = 'write_obfbdata_cl' 
     1579      CHARACTER(len=64) :: & 
     1580              & cdate, &   !: class 4 file validity date  
     1581              & cconf, &   !: model configuration 
     1582              & csys, &    !: model system 
     1583              & ccont, &   !: contact email 
     1584              & cinst, &   !: institution 
     1585              & cversion   !: model version 
     1586      CHARACTER(len=8) :: & 
     1587              & ckind      !: observation kind 
     1588      CHARACTER(len=3) :: cfield 
     1589      INTEGER :: kobs, &   !: number of observations 
     1590              &  kvars, &  !: number of physical variables 
     1591              &  kdeps, &  !: number of observed depths 
     1592              &  kfcst, &  !: number of forecasts 
     1593              &  kifcst, & !: current forecast number 
     1594              &  kproc     !: processor number 
     1595      INTEGER, DIMENSION(:, :, :), ALLOCATABLE :: & 
     1596              &  kqc       !: quality control counterpart 
     1597      INTEGER(KIND=2), DIMENSION(:, :, :), ALLOCATABLE :: & 
     1598              &  k2qc       !: quality control counterpart 
     1599      REAL(kind=fbdp) :: & 
     1600              &  pmodjuld  !: model Julian day 
     1601      REAL(kind=fbdp), DIMENSION(:), ALLOCATABLE :: & 
     1602              &  plead, &  !: forecast lead time 
     1603              &  plam, &   !: longitude of observation 
     1604              &  pphi, &   !: latitude of observation 
     1605              &  ptim      !: time of observation 
     1606      REAL(kind=fbdp), DIMENSION(:, :), ALLOCATABLE :: & 
     1607              &  pdep      !: depths of observations 
     1608      REAL(kind=fbdp), DIMENSION(:, :, :), ALLOCATABLE :: & 
     1609              &  pob, &    !: observation counterpart 
     1610              &  pextra    !: extra field counterpart 
     1611      REAL(kind=fbdp), DIMENSION(:, :, :), ALLOCATABLE :: & 
     1612              &  pmod      !: model counterpart 
     1613      CHARACTER(len=128) :: & 
     1614              &  clfilename  !: class 4 file name 
     1615      CHARACTER(len=128), DIMENSION(:), ALLOCATABLE :: & 
     1616              &  ctype       !: Instrument type 
     1617      CHARACTER(len=nf90_max_name) :: & 
     1618              & cdtmp        !: NetCDF variable name 
     1619      CHARACTER(len=8), DIMENSION(:), ALLOCATABLE :: & 
     1620              &  cwmo, &     !: Instrument WMO ID 
     1621              &  cunit, &    !: Instrument WMO ID 
     1622              &  cvarname    !: Instrument WMO ID 
     1623      INTEGER :: & 
     1624              &  idep, &     !: Loop variable 
     1625              &  ivar, &     !: Loop variable 
     1626              &  iobs, &     !: Loop variable 
     1627              &  ii, &       !: Loop variable 
     1628              &  ij, &       !: Loop variable 
     1629              &  ik, &       !: Loop variable 
     1630              &  il          !: Loop variable 
     1631      cconf = TRIM(cl4_cfg) 
     1632      csys = TRIM(cl4_sys) 
     1633      cversion = TRIM(cl4_vn) 
     1634      ccont = TRIM(cl4_contact) 
     1635      cinst = TRIM(cl4_inst) 
     1636      cdate = TRIM(cl4_date) 
     1637      CALL locate_kind(cdfilename, ckind) 
     1638      kproc = narea 
     1639      kfcst = cl4_fcst_len 
     1640      kobs = fbdata%nobs 
     1641      kdeps = fbdata%nlev 
     1642      kvars = fbdata%nvar 
     1643      IF (kobs .GT. 0) THEN 
     1644         ALLOCATE(plam(kobs), & 
     1645               &  pphi(kobs), & 
     1646               &  ptim(kobs), & 
     1647               &  plead(kfcst), & 
     1648               &  pdep(kdeps, kobs), & 
     1649               &  kqc(kdeps, kvars, kobs), & 
     1650               &  k2qc(kdeps, kvars, kobs), & 
     1651               &  pob(kdeps, kvars, kobs), & 
     1652               &  pmod(kdeps, kvars, kobs), & 
     1653               &  pextra(kdeps, kvars, kobs), & 
     1654               &  ctype(kobs), & 
     1655               &  cwmo(kobs), & 
     1656               &  cunit(kvars), & 
     1657               &  cvarname(kvars)) 
     1658         plam(:) = fbdata%plam(:) 
     1659         pphi(:) = fbdata%pphi(:) 
     1660         ptim(:) = fbdata%ptim(:) 
     1661         pdep(:, :) = fbdata%pdep(:, :) 
     1662         kqc(:,:,:) = 1. 
     1663         DO ii = 1, kvars 
     1664            cvarname(ii)  = fbdata%cname(ii) 
     1665            cunit(ii)     = fbdata%cobunit(ii) 
     1666         END DO 
     1667 
     1668         ! Quality control algorithm 
     1669         k2qc(:,:,:) = NF90_FILL_SHORT 
     1670         DO idep = 1,kdeps 
     1671            DO ivar = 1, kvars 
     1672               DO iobs = 1, kobs 
     1673                  ! 1 symbolises good for fbdata 
     1674                  ! fbimdi symbolises that qc has not been set 
     1675                  ! Essentially, if any fbdata flag is not an element of {1, fbimdi} 
     1676                  ! then set the class 4 flag to bad. 
     1677                  ! Note: fbdata%ioqc is marked good if zero. 
     1678                  IF (((fbdata%ioqc(iobs) /= 0) .AND. & 
     1679                            & (fbdata%ioqc(iobs) /= fbimdi)) .OR. & 
     1680                    & ((fbdata%ipqc(iobs) /= 1) .AND. & 
     1681                            & (fbdata%ipqc(iobs) /= fbimdi)) .OR. & 
     1682                    & ((fbdata%idqc(idep,iobs) /= 1) .AND. & 
     1683                            & (fbdata%idqc(idep,iobs) /= fbimdi)) .OR. & 
     1684                    & ((fbdata%ivqc(iobs,ivar) /= 1) .AND. & 
     1685                            & (fbdata%ivqc(iobs,ivar) /= fbimdi)) .OR. & 
     1686                    & ((fbdata%ivlqc(idep,iobs,ivar) /= 1) .AND. & 
     1687                            & (fbdata%ivlqc(idep,iobs,ivar) /= fbimdi)) .OR. & 
     1688                    & ((fbdata%itqc(iobs) /= 1) .AND. & 
     1689                            & (fbdata%itqc(iobs) /= fbimdi))) THEN 
     1690                     ! 1 symbolises bad for class 4 file 
     1691                     k2qc(idep, ivar, iobs) = 1 
     1692                  ELSE 
     1693                     ! 0 symbolises good for class 4 file 
     1694                     k2qc(idep, ivar, iobs) = 0 
     1695                  END IF  
     1696               END DO 
     1697            END DO 
     1698         END DO 
     1699 
     1700         ! Permute observation dimensions 
     1701         pob(:,:,:) = RESHAPE(fbdata%pob, (/kdeps, kvars, kobs/), & 
     1702                            & ORDER=(/1, 3, 2/)) 
     1703 
     1704         ! Explicit model counterpart dimension permutation 
     1705         ! 1,2,3,4 --> 1,4,2,3 
     1706         pmod(:,:,:) = fbrmdi 
     1707         ij = cl4_fcst_idx(jimatch) 
     1708         DO ii = 1,kdeps 
     1709            DO ik = 1, kvars 
     1710               DO il = 1, kobs 
     1711                  pmod(ii,ik,il) = fbdata%padd(ii,il,1,ik) 
     1712               END DO 
     1713            END DO 
     1714         END DO 
     1715 
     1716         ! Extra fields set to missing for now 
     1717         pextra(:,:,:) = fbrmdi 
     1718 
     1719         ! Lead time of class 4 file is a global parameter 
     1720         plead = cl4_leadtime(1:cl4_fcst_len) 
     1721 
     1722         ! Model Julian day 
     1723         pmodjuld = cl4_modjuld 
     1724 
     1725         ! Observation types 
     1726         ctype(:) = 'X' 
     1727         DO ii = 1,kobs 
     1728            ctype(ii) = fbdata%cdtyp(ii) 
     1729         END DO 
     1730 
     1731         ! World Meteorology Organisation codes 
     1732         cwmo(:) = fbdata%cdwmo(:) 
     1733 
     1734         ! Initialise class 4 file 
     1735         CALL ooo_wri_init(cconf, csys, ckind, cversion, ccont, cinst, cdate, & 
     1736                         & kproc, kobs, kvars, kdeps, kfcst, & 
     1737                         & clfilename) 
     1738 
     1739         ! Write standard variables 
     1740         CALL ooo_wri_default(clfilename, kobs, kvars, kfcst, kdeps, & 
     1741                            & ctype, cwmo, cunit, cvarname, & 
     1742                            & plam, pphi, pdep, ptim, pob, plead, & 
     1743                            & k2qc, pmodjuld) 
     1744         !! Write to optional variables 
     1745         cdtmp = cl4_vars(jimatch) 
     1746         IF ( (TRIM(cdtmp) == "forecast") .OR. & 
     1747              (TRIM(cdtmp) == "persistence") ) THEN 
     1748            !! 4D variables 
     1749            CALL ooo_wri_extra(clfilename, TRIM(cdtmp), kdeps, kfcst, & 
     1750                            &  kvars, kobs, (/ 1,ij,1,1 /), (/ kdeps,1,kvars,kobs /), pmod) 
     1751         ELSE 
     1752            !! 3D variables 
     1753            CALL ooo_wri_extra(clfilename, TRIM(cdtmp), kdeps, & 
     1754                            &  kvars, kobs, (/ 1,1,1 /), (/ kdeps,kvars,kobs /), pmod) 
     1755         ENDIF 
     1756 
     1757         DEALLOCATE(plam, pphi, ptim, pdep, plead, kqc, k2qc, & 
     1758                  & pob, pmod, pextra, ctype, cwmo, & 
     1759                  & cunit, cvarname) 
     1760      END IF 
     1761   END SUBROUTINE write_obfbdata_cl 
     1762#endif 
     1763 
     1764#if defined key_offobsoper 
     1765   SUBROUTINE locate_kind(cdfilename, ckind) 
     1766      !!---------------------------------------------------------------------- 
     1767      !!                    ***  ROUTINE locate_kind  *** 
     1768      !! 
     1769      !! ** Purpose : Detect which kind of class 4 file is being produced. 
     1770      !! 
     1771      !! ** Method  : 1. Inspect cdfilename for observation kind. 
     1772      !!---------------------------------------------------------------------- 
     1773      CHARACTER(len=*) :: cdfilename ! Feedback filename 
     1774      CHARACTER(len=8) :: ckind 
     1775      IF (cdfilename(1:3) == 'sst') THEN 
     1776         ckind = 'SST' 
     1777      ELSE IF (cdfilename(1:3) == 'sla') THEN 
     1778         ckind = 'SLA' 
     1779      ELSE IF (cdfilename(1:3) == 'pro') THEN 
     1780         ckind = 'profile' 
     1781      ELSE IF (cdfilename(1:3) == 'ena') THEN 
     1782         ckind = 'profile' 
     1783      ELSE IF (cdfilename(1:3) == 'sea') THEN 
     1784         ckind = 'seaice' 
     1785      ELSE 
     1786         ckind = 'unknown' 
     1787      END IF 
     1788   END SUBROUTINE locate_kind 
     1789#endif 
    15271790 
    15281791   SUBROUTINE putvaratt_obfbdata( idfile, idvar, cdlongname, cdunits, & 
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/OBS/obs_oper.F90

    r3651 r4229  
    861861 
    862862         ENDIF 
    863           
    864863         sstdatqc%rmod(jobs,1) = zext(1) 
    865864          
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/SBC/fldread.F90

    r3851 r4229  
    2121   USE lib_mpp         ! MPP library 
    2222   USE wrk_nemo        ! work arrays 
     23   USE lbclnk          ! ocean lateral boundary conditions (C1D case) 
    2324   USE ioipsl, ONLY :   ymds2ju, ju2ymds   ! for calendar 
    2425 
     
    3132   TYPE, PUBLIC ::   FLD_N      !: Namelist field informations 
    3233      CHARACTER(len = 256) ::   clname      ! generic name of the NetCDF flux file 
    33       INTEGER              ::   nfreqh      ! frequency of each flux file 
     34      REAL(wp)             ::   nfreqh      ! frequency of each flux file 
    3435      CHARACTER(len = 34)  ::   clvar       ! generic name of the variable in the NetCDF flux file 
    3536      LOGICAL              ::   ln_tint     ! time interpolation or not (T/F) 
     
    4546      CHARACTER(len = 256)            ::   clrootname   ! generic name of the NetCDF file 
    4647      CHARACTER(len = 256)            ::   clname       ! current name of the NetCDF file 
    47       INTEGER                         ::   nfreqh       ! frequency of each flux file 
     48      REAL(wp)                        ::   nfreqh       ! frequency of each flux file 
    4849      CHARACTER(len = 34)             ::   clvar        ! generic name of the variable in the NetCDF flux file 
    4950      LOGICAL                         ::   ln_tint      ! time interpolation or not (T/F) 
     
    193194                  sd(jf)%fdta(:,:,:,1) = sd(jf)%fdta(:,:,:,2)   ! re-swap before record field 
    194195                  sd(jf)%nrec_b(1) = sd(jf)%nrec_a(1)           ! update before record informations 
    195                   sd(jf)%nrec_b(2) = sd(jf)%nrec_a(2) - sd(jf)%nfreqh * 3600  ! assume freq to be in hours in this case 
     196                  sd(jf)%nrec_b(2) = sd(jf)%nrec_a(2) - NINT( sd(jf)%nfreqh * 3600 )  ! assume freq to be in hours in this case 
    196197                  sd(jf)%rotn(1)   = sd(jf)%rotn(2)             ! update before rotate informations 
    197198                  sd(jf)%nrec_a(1) = itmp                       ! move back to after record  
     
    211212                     sd(jf)%fdta(:,:,:,1) = sd(jf)%fdta(:,:,:,2)   ! re-swap before record field 
    212213                     sd(jf)%nrec_b(1) = sd(jf)%nrec_a(1)           ! update before record informations 
    213                      sd(jf)%nrec_b(2) = sd(jf)%nrec_a(2) - sd(jf)%nfreqh * 3600  ! assume freq to be in hours in this case 
     214                     sd(jf)%nrec_b(2) = sd(jf)%nrec_a(2) - NINT( sd(jf)%nfreqh * 3600 )  ! assume freq to be in hours in this case 
    214215                     sd(jf)%rotn(1)   = sd(jf)%rotn(2)             ! update before rotate informations 
    215216                     sd(jf)%nrec_a(1) = sd(jf)%nrec_a(1) + 1       ! move back to after record 
     
    264265            IF( sd(jf)%ln_tint ) THEN              ! temporal interpolation 
    265266               IF(lwp .AND. kt - nit000 <= 100 ) THEN  
    266                   clfmt = "('fld_read: var ', a, ' kt = ', i8, ' (', f7.2,' days), Y/M/D = ', i4.4,'/', i2.2,'/', i2.2," //   & 
    267                      &    "', records b/a: ', i4.4, '/', i4.4, ' (days ', f7.2,'/', f7.2, ')')" 
     267                  clfmt = "('fld_read: var ', a, ' kt = ', i8, ' (', f9.4,' days), Y/M/D = ', i4.4,'/', i2.2,'/', i2.2," //   & 
     268                     &    "', records b/a: ', i6.4, '/', i6.4, ' (days ', f9.4,'/', f9.4, ')')" 
    268269                  WRITE(numout, clfmt)  TRIM( sd(jf)%clvar ), kt, REAL(isecsbc,wp)/rday, nyear, nmonth, nday,   &             
    269270                     & sd(jf)%nrec_b(1), sd(jf)%nrec_a(1), REAL(sd(jf)%nrec_b(2),wp)/rday, REAL(sd(jf)%nrec_a(2),wp)/rday 
     
    277278            ELSE   ! nothing to do... 
    278279               IF(lwp .AND. kt - nit000 <= 100 ) THEN 
    279                   clfmt = "('fld_read: var ', a, ' kt = ', i8,' (', f7.2,' days), Y/M/D = ', i4.4,'/', i2.2,'/', i2.2," //   & 
    280                      &    "', record: ', i4.4, ' (days ', f7.2, ' <-> ', f7.2, ')')" 
     280                  clfmt = "('fld_read: var ', a, ' kt = ', i8,' (', f9.4,' days), Y/M/D = ', i4.4,'/', i2.2,'/', i2.2," //   & 
     281                     &    "', record: ', i6.4, ' (days ', f9.4, ' <-> ', f9.4, ')')" 
    281282                  WRITE(numout, clfmt) TRIM(sd(jf)%clvar), kt, REAL(isecsbc,wp)/rday, nyear, nmonth, nday,    & 
    282283                     &                 sd(jf)%nrec_a(1), REAL(sd(jf)%nrec_b(2),wp)/rday, REAL(sd(jf)%nrec_a(2),wp)/rday 
     
    349350            ELSE                                ! higher frequency mean (in hours)  
    350351               IF    ( sdjf%cltype      == 'monthly' ) THEN   ! monthly file 
    351                   sdjf%nrec_a(1) = 24 * nmonth_len(nmonth-1) / sdjf%nfreqh                 ! last record of previous month 
     352                  sdjf%nrec_a(1) = NINT( 24 * nmonth_len(nmonth-1) / sdjf%nfreqh )         ! last record of previous month 
    352353                  llprevmth = .TRUE.                                                       ! use previous month file? 
    353354                  llprevyr  = llprevmth .AND. nmonth == 1                                  ! use previous year  file? 
    354355               ELSEIF( sdjf%cltype(1:4) == 'week'    ) THEN   ! weekly file 
    355356                  llprevweek = .TRUE.                                                      ! use previous week  file? 
    356                   sdjf%nrec_a(1) = 24 * 7 / sdjf%nfreqh                                    ! last record of previous week 
     357                  sdjf%nrec_a(1) = NINT( 24 * 7 / sdjf%nfreqh )                            ! last record of previous week 
    357358                  isec_week = NINT(rday) * 7                                               ! add a shift toward previous week 
    358359               ELSEIF( sdjf%cltype      == 'daily'   ) THEN   ! daily file 
    359                   sdjf%nrec_a(1) = 24 / sdjf%nfreqh                                        ! last record of previous day 
     360                  sdjf%nrec_a(1) = NINT( 24 / sdjf%nfreqh )                                ! last record of previous day 
    360361                  llprevday = .TRUE.                                                       ! use previous day   file? 
    361362                  llprevmth = llprevday .AND. nday   == 1                                  ! use previous month file? 
    362363                  llprevyr  = llprevmth .AND. nmonth == 1                                  ! use previous year  file? 
    363364               ELSE                                           ! yearly file 
    364                   sdjf%nrec_a(1) = 24 * nyear_len(0) / sdjf%nfreqh                         ! last record of previous year  
     365                  sdjf%nrec_a(1) = NINT( 24 * nyear_len(0) / sdjf%nfreqh )                 ! last record of previous year  
    365366                  llprevyr = .NOT. sdjf%ln_clim                                            ! use previous year  file? 
    366367               ENDIF 
     
    401402         CALL fld_get( sdjf, map ) 
    402403 
    403          clfmt = "('fld_init : time-interpolation for ', a, ' read previous record = ', i4, ' at time = ', f7.2, ' days')" 
     404         clfmt = "('fld_init : time-interpolation for ', a, ' read previous record = ', i6, ' at time = ', f7.2, ' days')" 
    404405         IF(lwp) WRITE(numout, clfmt) TRIM(sdjf%clvar), sdjf%nrec_a(1), REAL(sdjf%nrec_a(2),wp)/rday 
    405406 
     
    511512         !                                   ! ================================ ! 
    512513         ! 
    513          ifreq_sec = sdjf%nfreqh * 3600                                                 ! frequency mean (in seconds) 
     514         ifreq_sec = NINT( sdjf%nfreqh * 3600 )                                         ! frequency mean (in seconds) 
    514515         IF( sdjf%cltype(1:4) == 'week' )   isec_week = ksec_week( sdjf%cltype(6:8) )   ! since the first day of the current week 
    515516         ! number of second since the beginning of the file 
     
    581582      INTEGER                  ::   iw     ! index into wgts array 
    582583      INTEGER                  ::   ipdom  ! index of the domain 
     584      INTEGER                  ::   idvar  ! variable ID 
     585      INTEGER                  ::   idmspc ! number of spatial dimensions 
     586      LOGICAL                  ::   lmoor  ! C1D case: point data 
    583587      !!--------------------------------------------------------------------- 
    584588      ! 
     
    598602         ELSE                                  ;  ipdom = jpdom_unknown 
    599603         ENDIF 
     604         ! C1D case: If product of spatial dimensions == ipk, then x,y are of 
     605         ! size 1 (point/mooring data): this must be read onto the central grid point 
     606         idvar  = iom_varid( sdjf%num, sdjf%clvar ) 
     607         idmspc = iom_file( sdjf%num )%ndims( idvar ) 
     608         IF( iom_file( sdjf%num )%luld( idvar ) )   idmspc = idmspc - 1 
     609         lmoor  = (idmspc == 0 .OR. PRODUCT( iom_file( sdjf%num )%dimsz( 1:MAX(idmspc,1) ,idvar ) ) == ipk) 
     610         ! 
    600611         SELECT CASE( ipk ) 
    601612         CASE(1) 
    602             IF( sdjf%ln_tint ) THEN   ;   CALL iom_get( sdjf%num, ipdom, sdjf%clvar, sdjf%fdta(:,:,1,2), sdjf%nrec_a(1) ) 
    603             ELSE                      ;   CALL iom_get( sdjf%num, ipdom, sdjf%clvar, sdjf%fnow(:,:,1  ), sdjf%nrec_a(1) ) 
     613            IF( lk_c1d .AND. lmoor ) THEN 
     614               IF( sdjf%ln_tint ) THEN 
     615                  CALL iom_get( sdjf%num, sdjf%clvar, sdjf%fdta(2,2,1,2), sdjf%nrec_a(1) ) 
     616                  CALL lbc_lnk( sdjf%fdta(:,:,1,2),'Z',1. ) 
     617               ELSE 
     618                  CALL iom_get( sdjf%num, sdjf%clvar, sdjf%fnow(2,2,1  ), sdjf%nrec_a(1) ) 
     619                  CALL lbc_lnk( sdjf%fnow(:,:,1  ),'Z',1. ) 
     620               ENDIF 
     621            ELSE 
     622               IF( sdjf%ln_tint ) THEN   ;   CALL iom_get( sdjf%num, ipdom, sdjf%clvar, sdjf%fdta(:,:,1,2), sdjf%nrec_a(1) ) 
     623               ELSE                      ;   CALL iom_get( sdjf%num, ipdom, sdjf%clvar, sdjf%fnow(:,:,1  ), sdjf%nrec_a(1) ) 
     624               ENDIF 
    604625            ENDIF 
    605626         CASE DEFAULT 
    606             IF( sdjf%ln_tint ) THEN   ;   CALL iom_get( sdjf%num, ipdom, sdjf%clvar, sdjf%fdta(:,:,:,2), sdjf%nrec_a(1) ) 
    607             ELSE                      ;   CALL iom_get( sdjf%num, ipdom, sdjf%clvar, sdjf%fnow(:,:,:  ), sdjf%nrec_a(1) ) 
     627            IF (lk_c1d .AND. lmoor ) THEN 
     628               IF( sdjf%ln_tint ) THEN 
     629                  CALL iom_get( sdjf%num, jpdom_unknown, sdjf%clvar, sdjf%fdta(2,2,:,2), sdjf%nrec_a(1) ) 
     630                  CALL lbc_lnk( sdjf%fdta(:,:,:,2),'Z',1. ) 
     631               ELSE 
     632                  CALL iom_get( sdjf%num, jpdom_unknown, sdjf%clvar, sdjf%fnow(2,2,:  ), sdjf%nrec_a(1) ) 
     633                  CALL lbc_lnk( sdjf%fnow(:,:,:  ),'Z',1. ) 
     634               ENDIF 
     635            ELSE 
     636               IF( sdjf%ln_tint ) THEN   ;   CALL iom_get( sdjf%num, ipdom, sdjf%clvar, sdjf%fdta(:,:,:,2), sdjf%nrec_a(1) ) 
     637               ELSE                      ;   CALL iom_get( sdjf%num, ipdom, sdjf%clvar, sdjf%fnow(:,:,:  ), sdjf%nrec_a(1) ) 
     638               ENDIF 
    608639            ENDIF 
    609640         END SELECT 
     
    817848            ENDIF 
    818849         ELSE                                                                       ! higher frequency mean (in hours) 
    819             IF(     sdjf%cltype      == 'monthly' ) THEN   ;   sdjf%nreclast = 24 * imonth_len / sdjf%nfreqh  
    820             ELSEIF( sdjf%cltype(1:4) == 'week'    ) THEN   ;   sdjf%nreclast = 24 * 7          / sdjf%nfreqh 
    821             ELSEIF( sdjf%cltype      == 'daily'   ) THEN   ;   sdjf%nreclast = 24              / sdjf%nfreqh 
    822             ELSE                                           ;   sdjf%nreclast = 24 * iyear_len  / sdjf%nfreqh  
     850            IF(     sdjf%cltype      == 'monthly' ) THEN   ;   sdjf%nreclast = NINT( 24 * imonth_len / sdjf%nfreqh ) 
     851            ELSEIF( sdjf%cltype(1:4) == 'week'    ) THEN   ;   sdjf%nreclast = NINT( 24 * 7          / sdjf%nfreqh ) 
     852            ELSEIF( sdjf%cltype      == 'daily'   ) THEN   ;   sdjf%nreclast = NINT( 24              / sdjf%nfreqh ) 
     853            ELSE                                           ;   sdjf%nreclast = NINT( 24 * iyear_len  / sdjf%nfreqh ) 
    823854            ENDIF 
    824855         ENDIF 
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/SBC/sbcblk_core.F90

    r3772 r4229  
    7373 
    7474   !                                  !!* Namelist namsbc_core : CORE bulk parameters 
    75    LOGICAL  ::   ln_2m     = .FALSE.   ! logical flag for height of air temp. and hum 
     75   LOGICAL  ::   ln_2m     = .FALSE.   ! logical flag for case where z(q,t) = 2m and z(u) = 10m 
     76   LOGICAL  ::   ln_bulk2z = .FALSE.   ! logical flag for case where z(q,t) and z(u) are specified in the namelist 
     77   REAL(wp) ::   rn_zqt    = 10.       ! z(q,t) : height of humidity and temperature measurements 
     78   REAL(wp) ::   rn_zu     = 10.       ! z(u)   : height of wind measurements 
    7679   LOGICAL  ::   ln_taudif = .FALSE.   ! logical flag to use the "mean of stress module - module of mean stress" data 
    7780   REAL(wp) ::   rn_pfac   = 1.        ! multiplication factor for precipitation 
     
    129132      NAMELIST/namsbc_core/ cn_dir , ln_2m  , ln_taudif, rn_pfac,           & 
    130133         &                  sn_wndi, sn_wndj, sn_humi  , sn_qsr ,           & 
    131          &                  sn_qlw , sn_tair, sn_prec  , sn_snow, sn_tdif 
     134         &                  sn_qlw , sn_tair, sn_prec  , sn_snow,           & 
     135         &                  sn_tdif, rn_zqt , ln_bulk2z, rn_zu 
    132136      !!--------------------------------------------------------------------- 
    133137 
     
    319323            &                      Cd    , Ch              , Ce  ,   & 
    320324            &                      zt_zu , zq_zu                   ) 
     325      ELSE IF( ln_bulk2z ) THEN 
     326         !! If the height of the air temp./spec. hum. and wind are to be specified by hand : 
     327         IF( rn_zqt == rn_zu ) THEN 
     328            !! If air temp. and spec. hum. are at the same height as wind : 
     329            CALL TURB_CORE_1Z( rn_zu, zst   , sf(jp_tair)%fnow(:,:,1),       & 
     330               &                      zqsatw, sf(jp_humi)%fnow(:,:,1), wndm, & 
     331               &                      Cd    , Ch                     , Ce  ) 
     332         ELSE 
     333            !! If air temp. and spec. hum. are at a different height to wind : 
     334            CALL TURB_CORE_2Z(rn_zqt, rn_zu , zst   , sf(jp_tair)%fnow,         & 
     335               &                              zqsatw, sf(jp_humi)%fnow, wndm,   & 
     336               &                              Cd    , Ch              , Ce  ,   & 
     337               &                              zt_zu , zq_zu                 ) 
     338         ENDIF 
    321339      ELSE 
    322340         !! If air temp. and spec. hum. are given at same height than wind (10m) : 
     
    363381      !  Turbulent fluxes over ocean 
    364382      ! ----------------------------- 
    365       IF( ln_2m ) THEN 
    366          ! Values of temp. and hum. adjusted to 10m must be used instead of 2m values 
     383      IF( ln_2m .OR. ( ln_bulk2z .AND. rn_zqt /= rn_zu ) ) THEN 
     384         ! Values of temp. and hum. adjusted to height of wind must be used 
    367385         zevap(:,:) = MAX( 0.e0, rhoa    *Ce(:,:)*( zqsatw(:,:) - zq_zu(:,:) ) * wndm(:,:) )   ! Evaporation 
    368386         zqsb (:,:) =            rhoa*cpa*Ch(:,:)*( zst   (:,:) - zt_zu(:,:) ) * wndm(:,:)     ! Sensible Heat 
     
    786804      !!      Momentum, Latent and sensible heat exchange coefficients 
    787805      !!      Caution: this procedure should only be used in cases when air 
    788       !!      temperature (T_air) and air specific humidity (q_air) are at 2m 
    789       !!      whereas wind (dU) is at 10m. 
     806      !!      temperature (T_air) and air specific humidity (q_air) are at a 
     807      !!      different height to wind (dU). 
    790808      !! 
    791809      !! References :   Large & Yeager, 2004 : ??? 
     
    805823 
    806824      INTEGER :: j_itt 
    807       INTEGER , PARAMETER :: nb_itt = 3              ! number of itterations 
     825      INTEGER , PARAMETER :: nb_itt = 5              ! number of itterations 
    808826      REAL(wp), PARAMETER ::   grav   = 9.8          ! gravity                        
    809827      REAL(wp), PARAMETER ::   kappa  = 0.4          ! von Karman's constant 
     
    902920           !! 
    903921           !! Shifting the neutral 10m transfer coefficients to (zu,zeta_u) : 
    904            xct = 1. + sqrt_Cd_n10/kappa*(log(zu/10.) - zpsi_m) 
     922           xct = 1. + sqrt_Cd_n10/kappa*(log(zu/10.) - zpsi_m)   ! L & Y eq. (10a) 
    905923           Cd = Cd_n10/(xct*xct) ; sqrt_Cd = sqrt(Cd) 
    906924         ENDIF 
     
    908926         xlogt = log(zu/10.) - zpsi_hu 
    909927         !! 
    910          xct = 1. + Ch_n10*xlogt/kappa/sqrt_Cd_n10 
     928         xct = 1. + Ch_n10*xlogt/kappa/sqrt_Cd_n10               ! L & Y eq. (10b) 
    911929         Ch  = Ch_n10*sqrt_Cd/sqrt_Cd_n10/xct 
    912930         !! 
    913          xct = 1. + Ce_n10*xlogt/kappa/sqrt_Cd_n10 
     931         xct = 1. + Ce_n10*xlogt/kappa/sqrt_Cd_n10               ! L & Y eq. (10c) 
    914932         Ce  = Ce_n10*sqrt_Cd/sqrt_Cd_n10/xct 
    915933         !! 
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/TRA/tradmp.F90

    r3294 r4229  
    2727   USE oce            ! ocean: variables 
    2828   USE dom_oce        ! ocean: domain variables 
     29   USE c1d            ! 1D vertical configuration 
    2930   USE trdmod_oce     ! ocean: trend variables 
    3031   USE trdtra         ! active tracers: trends 
     
    4445   PUBLIC   tra_dmp      ! routine called by step.F90 
    4546   PUBLIC   tra_dmp_init ! routine called by opa.F90 
    46    PUBLIC   dtacof       ! routine called by in both tradmp.F90 and trcdmp.F90 
    47    PUBLIC   dtacof_zoom  ! routine called by in both tradmp.F90 and trcdmp.F90 
     47   PUBLIC   dtacof       ! routine called by tradmp.F90, trcdmp.F90 and dyndmp.F90 
     48   PUBLIC   dtacof_zoom  ! routine called by tradmp.F90, trcdmp.F90 and dyndmp.F90 
    4849 
    4950   !                                !!* Namelist namtra_dmp : T & S newtonian damping * 
    50    LOGICAL, PUBLIC ::   ln_tradmp = .TRUE.    !: internal damping flag 
    51    INTEGER         ::   nn_hdmp   =   -1      ! = 0/-1/'latitude' for damping over T and S 
    52    INTEGER         ::   nn_zdmp   =    0      ! = 0/1/2 flag for damping in the mixed layer 
    53    REAL(wp)        ::   rn_surf   =   50._wp  ! surface time scale for internal damping        [days] 
    54    REAL(wp)        ::   rn_bot    =  360._wp  ! bottom time scale for internal damping         [days] 
    55    REAL(wp)        ::   rn_dep    =  800._wp  ! depth of transition between rn_surf and rn_bot [meters] 
    56    INTEGER         ::   nn_file   =    2      ! = 1 create a damping.coeff NetCDF file  
     51   LOGICAL , PUBLIC ::   ln_tradmp = .TRUE.    !: internal damping flag 
     52   INTEGER , PUBLIC ::   nn_hdmp   =   -1      ! = 0/-1/'latitude' for damping over T and S 
     53   INTEGER , PUBLIC ::   nn_zdmp   =    0      ! = 0/1/2 flag for damping in the mixed layer 
     54   REAL(wp), PUBLIC ::   rn_surf   =   50._wp  ! surface time scale for internal damping        [days] 
     55   REAL(wp), PUBLIC ::   rn_bot    =  360._wp  ! bottom time scale for internal damping         [days] 
     56   REAL(wp), PUBLIC ::   rn_dep    =  800._wp  ! depth of transition between rn_surf and rn_bot [meters] 
     57   INTEGER , PUBLIC ::   nn_file   =    2      ! = 1 create a damping.coeff NetCDF file  
    5758 
    5859   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   strdmp   !: damping salinity trend (psu/s) 
     
    191192      !! ** Purpose :   Initialization for the newtonian damping  
    192193      !! 
    193       !! ** Method  :   read the nammbf namelist and check the parameters 
     194      !! ** Method  :   read the namtra_dmp namelist and check the parameters 
    194195      !!---------------------------------------------------------------------- 
    195196      NAMELIST/namtra_dmp/ ln_tradmp, nn_hdmp, nn_zdmp, rn_surf, rn_bot, rn_dep, nn_file 
     
    199200      READ   ( numnam, namtra_dmp ) 
    200201       
    201       IF( lzoom )   nn_zdmp = 0          ! restoring to climatology at closed north or south boundaries 
     202      IF( lzoom .AND. .NOT. lk_c1d )   nn_zdmp = 0          ! restoring to climatology at closed north or south boundaries 
    202203 
    203204      IF(lwp) THEN                       ! Namelist print 
     
    206207         WRITE(numout,*) '~~~~~~~' 
    207208         WRITE(numout,*) '   Namelist namtra_dmp : set damping parameter' 
    208          WRITE(numout,*) '      add a damping termn or not      ln_tradmp = ', ln_tradmp 
     209         WRITE(numout,*) '      add a damping term or not       ln_tradmp = ', ln_tradmp 
    209210         WRITE(numout,*) '      T and S damping option          nn_hdmp   = ', nn_hdmp 
    210          WRITE(numout,*) '      mixed layer damping option      nn_zdmp   = ', nn_zdmp, '(zoom: forced to 0)' 
     211         WRITE(numout,*) '      mixed layer damping option      nn_zdmp   = ', nn_zdmp, '(non-C1D zoom: forced to 0)' 
    211212         WRITE(numout,*) '      surface time scale (days)       rn_surf   = ', rn_surf 
    212213         WRITE(numout,*) '      bottom time scale (days)        rn_bot    = ', rn_bot 
     
    220221         IF( tra_dmp_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'tra_dmp_init: unable to allocate arrays' ) 
    221222         ! 
     223#if ! defined key_c1d 
    222224         SELECT CASE ( nn_hdmp ) 
    223225         CASE (  -1  )   ;   IF(lwp) WRITE(numout,*) '   tracer damping in the Med & Red seas only' 
     
    228230         END SELECT 
    229231         ! 
     232#endif 
    230233         SELECT CASE ( nn_zdmp ) 
    231234         CASE ( 0 )   ;   IF(lwp) WRITE(numout,*) '   tracer damping throughout the water column' 
     
    245248         ttrdmp(:,:,:) = 0._wp 
    246249         !                          ! Damping coefficients initialization 
    247          IF( lzoom ) THEN   ;   CALL dtacof_zoom( resto ) 
     250         IF( lzoom .AND. .NOT. lk_c1d ) THEN   ;   CALL dtacof_zoom( resto ) 
    248251         ELSE               ;   CALL dtacof( nn_hdmp, rn_surf, rn_bot, rn_dep, nn_file, 'TRA', resto ) 
    249252         ENDIF 
     
    353356      REAL(wp)                        , INTENT(in   )  ::  pn_dep     ! depth of transition (meters) 
    354357      INTEGER                         , INTENT(in   )  ::  kn_file    ! save the damping coef on a file or not 
    355       CHARACTER(len=3)                , INTENT(in   )  ::  cdtype     ! =TRA or TRC (tracer indicator) 
     358      CHARACTER(len=3)                , INTENT(in   )  ::  cdtype     ! =TRA, TRC or DYN (tracer/dynamics indicator) 
    356359      REAL(wp), DIMENSION(jpi,jpj,jpk), INTENT(inout)  ::  presto     ! restoring coeff. (s-1) 
    357360      ! 
     
    373376      CALL wrk_alloc( jpi, jpj, zmrs      ) 
    374377      CALL wrk_alloc( jpi, jpj, jpk, zdct ) 
     378#if defined key_c1d 
     379      !                                   ! ==================== 
     380      !                                   !  C1D configuration : local domain 
     381      !                                   ! ==================== 
     382      ! 
     383      IF(lwp) WRITE(numout,*) 
     384      IF(lwp) WRITE(numout,*) '              dtacof : C1D 3x3 local domain' 
     385      IF(lwp) WRITE(numout,*) '              -----------------------------' 
     386      ! 
     387      presto(:,:,:) = 0._wp 
     388      ! 
     389      zsdmp = 1._wp / ( pn_surf * rday ) 
     390      zbdmp = 1._wp / ( pn_bot  * rday ) 
     391      DO jk = 2, jpkm1 
     392         DO jj = 1, jpj 
     393            DO ji = 1, jpi 
     394               !   ONLY vertical variation from zsdmp (sea surface) to zbdmp (bottom) 
     395               presto(ji,jj,jk) = zbdmp + (zsdmp-zbdmp) * EXP(-fsdept(ji,jj,jk)/pn_dep) 
     396            END DO 
     397         END DO 
     398      END DO 
     399      ! 
     400      presto(:,:, : ) = presto(:,:,:) * tmask(:,:,:) 
     401#else 
    375402      !                                   ! ==================== 
    376403      !                                   !  ORCA configuration : global domain 
     
    552579         CALL ctl_stop( 'Choose a correct value of nn_hdmp or put ln_tradmp to FALSE' ) 
    553580      ENDIF 
     581#endif 
    554582 
    555583      !                            !--------------------------------! 
     
    559587         IF( cdtype == 'TRA' ) cfile = 'damping.coeff' 
    560588         IF( cdtype == 'TRC' ) cfile = 'damping.coeff.trc' 
     589         IF( cdtype == 'DYN' ) cfile = 'damping.coeff.dyn' 
    561590         cfile = TRIM( cfile ) 
    562591         CALL iom_open  ( cfile, inum0, ldwrt = .TRUE., kiolib = jprstlib ) 
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r3769 r4229  
    7676   USE c1d             ! 1D configuration 
    7777   USE step_c1d        ! Time stepping loop for the 1D configuration 
     78   USE dyndmp          ! Momentum damping 
    7879#if defined key_top 
    7980   USE trcini          ! passive tracer initialisation 
     
    328329                            CALL     phy_cst    ! Physical constants 
    329330                            CALL     eos_init   ! Equation of state 
     331      IF( lk_c1d        )   CALL     c1d_init   ! 1D column configuration 
    330332                            CALL     dom_cfg    ! Domain configuration 
    331333                            CALL     dom_init   ! Domain 
     
    368370                            CALL tra_bbc_init   ! bottom heat flux 
    369371      IF( lk_trabbl     )   CALL tra_bbl_init   ! advective (and/or diffusive) bottom boundary layer scheme 
    370       IF( ln_tradmp     )   CALL tra_dmp_init   ! internal damping trends 
     372                            CALL tra_dmp_init   ! internal damping trends- tracers 
    371373                            CALL tra_adv_init   ! horizontal & vertical advection 
    372374                            CALL tra_ldf_init   ! lateral mixing 
     
    374376 
    375377      !                                     ! Dynamics 
     378      IF( lk_c1d        )   CALL dyn_dmp_init   ! internal damping trends- momentum 
    376379                            CALL dyn_adv_init   ! advection (vector or flux form) 
    377380                            CALL dyn_vor_init   ! vorticity term including Coriolis 
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/par_AMM_12km.h90

    r3680 r4229  
    44   !!                  (AMM_12km configuration VN3.3) 
    55   !!--------------------------------------------------------------------- 
    6    CHARACTER (len=16)        & 
     6   CHARACTER (len=16)         & 
    77#if !defined key_agrif 
    8       , PARAMETER  & 
     8      , PARAMETER             & 
    99#endif 
    10       ::     
    11       cp_cfg = "amm"         !: name of the configuration 
    12    INTEGER                   & 
     10      ::                       
     11      cp_cfg  =  "amm"           !: Name of the configuration 
     12   INTEGER                    & 
    1313#if !defined key_agrif 
    14       , PARAMETER  & 
     14      , PARAMETER             & 
    1515#endif 
    16       ::     
    17       jp_cfg = 011  ,        &  !: resolution of the configuration (degrees) 
    18       ! Original data size 
    19       jpidta  = 198,        &  !: first horizontal dimension > or = to jpi 
    20       jpjdta  = 224,        &  !: second                     > or = to jpj 
    21       jpkdta  = 51,         &  !: number of levels           > or = to jpk 
    22       ! total domain matrix size 
    23       jpiglo  = jpidta,      &  !: first  dimension of global domain --> i 
    24       jpjglo  = jpjdta,      &  !: second dimension of global domain --> j 
    25       ! starting position of the zoom 
    26       jpizoom =   1   ,      &  !: left bottom (i,j) indices of the zoom 
    27       jpjzoom =   1   ,      &  !: in data indices 
     16      ::                      & 
     17      jp_cfg  =  011   ,      &  !: Resolution of the configuration (degrees) 
     18 
     19      ! Data domain size         !!! *  Size of all input files  * 
     20      jpidta  =  198   ,      &  !: 1st lateral dimension ( >= jpiglo ) 
     21      jpjdta  =  224   ,      &  !: 2nd lateral dimension ( >= jpjglo ) 
     22      jpkdta  =  51    ,      &  !: Number of levels      ( >= jpk    ) 
     23 
     24#if defined key_c1d 
     25      ! Zoom domain size         !!! *  C1D zoom  * 
     26      jpiglo  =  3     ,      &  !: 1st dimension of global domain --> i 
     27      jpjglo  =  3     ,      &  !: 2nd dimension of global domain --> j 
    2828      ! Domain characteristics 
    29       jperio  =    0            !: lateral cond. type (between 0 and 6) 
     29      jperio  =  0               !: Lateral cond. type (between 0 and 6) 
     30 
     31   INTEGER                    & 
     32      ::                      & 
     33      ! Starting position of the zoom 
     34      jpizoom =  1     ,      &  !: Left bottom (i,j) indices of the zoom 
     35      jpjzoom =  1               !: in data domain indices 
     36#else 
     37      ! Global domain size       !!! *  Global domain  * 
     38      jpiglo  =  jpidta,      &  !: 1st dimension of global domain --> i 
     39      jpjglo  =  jpjdta,      &  !: 2nd dimension of global domain --> j 
     40      ! Starting position of the zoom 
     41      jpizoom =  1     ,      &  !: Left bottom (i,j) indices of the zoom 
     42      jpjzoom =  1     ,      &  !: in data domain indices 
     43      ! Domain characteristics 
     44      jperio  =  0               !: Lateral cond. type (between 0 and 6) 
     45#endif 
     46 
    3047 
    3148   !!  Values set to pp_not_used indicates that this parameter is not used in THIS config. 
    3249   !!  Values set to pp_to_be_computed  indicates that variables will be computed in domzgr 
    33    REAL,PARAMETER      ::  pp_not_used = 999999_wp , & 
    34       &                    pp_to_be_computed = 0._wp 
    35    !! 
    36    !! Coefficients associated with the horizontal coordinate system (jphgr_msh /= 0 ) 
    37    !! 
    38    INTEGER, PARAMETER ::     & ! 
    39       jphgr_msh = 0            !: type of horizontal mesh 
    40       !                        !  = 0 curvilinear coordinate on the sphere 
    41       !                        !      read in coordinate.nc file 
    42       !                        !  = 1 geographical mesh on the sphere 
    43       !                        !      with regular grid-spacing 
    44       !                        !  = 2 f-plane with regular grid-spacing 
    45       !                        !  = 3 beta-plane with regular grid-spacing 
    46       !                        !  = 4 Mercator grid with T/U point at the equator  with 
    47       !                        !      isotropic resolution (e1_deg) 
     50 
     51   REAL(wp), PARAMETER ::              & 
     52      pp_not_used       = 999999._wp , &  !: 
     53      pp_to_be_computed = 0._wp           !: 
     54 
     55 
     56   !! Coefficients associated with the horizontal coordinate system 
     57 
     58   INTEGER, PARAMETER  ::     & 
     59      jphgr_msh = 0              !: type of horizontal mesh 
     60      !                          !: = 0 curvilinear coordinate on the sphere 
     61      !                          !:     read in coordinate.nc file 
     62      !                          !: = 1 geographical mesh on the sphere 
     63      !                          !:     with regular grid-spacing 
     64      !                          !: = 2 f-plane with regular grid-spacing 
     65      !                          !: = 3 beta-plane with regular grid-spacing 
     66      !                          !: = 4 Mercator grid with T/U point at the equator  with 
     67      !                          !:     isotropic resolution (e1_deg) 
    4868 
    4969      !   ppglam0 , ppgphi0: coordinates of the lower leftmost T point of the grid. 
    5070      !   The mercator grid starts only approximately at gphi0 because 
    5171      !   of the constraint that the equator be a T point. 
    52    REAL(wp), PARAMETER ::       &  ! 
    53       ppglam0  = pp_not_used,   &  !: longitude of first raw and column T-point (jphgr_msh = 1) 
    54       ppgphi0  = pp_not_used,   &  !: latitude  of first raw and column T-point (jphgr_msh = 1) 
    55       !                            !  latitude for the Coriolis or Beta parameter (jphgr_msh = 2 or 3) 
    56       ppe1_deg = pp_not_used,   &  !: zonal      grid-spacing (degrees) 
    57       ppe2_deg = pp_not_used,   &  !: meridional grid-spacing (degrees) 
     72 
     73   REAL(wp), PARAMETER ::     & 
     74      ppglam0  = pp_not_used, &  !: longitude of first raw and column T-point   (jphgr_msh = 1) 
     75      ppgphi0  = pp_not_used, &  !: latitude  of first raw and column T-point   (jphgr_msh = 1) 
     76      !                          !: latitude for the Coriolis or Beta parameter (jphgr_msh = 2 or 3) 
     77      ppe1_deg = pp_not_used, &  !: zonal      grid-spacing (degrees) 
     78      ppe2_deg = pp_not_used, &  !: meridional grid-spacing (degrees) 
    5879      ! 
    59       ppe1_m   = pp_not_used,   &  !: zonal      grid-spacing (meters ) 
    60       ppe2_m   = pp_not_used       !: meridional grid-spacing (meters ) 
     80      ppe1_m   = pp_not_used, &  !: zonal      grid-spacing (meters ) 
     81      ppe2_m   = pp_not_used     !: meridional grid-spacing (meters ) 
    6182 
    62    !! 
    63    !! Vertical grid parameter for domzgr 
    64    !! ================================== 
    65    !! 
    66    REAL(wp), PARAMETER  ::       & 
    67       &     ppsur = pp_to_be_computed ,  &  !: Computed in domzgr, set ppdzmin and pphmax below 
    68       &     ppa0  = pp_to_be_computed ,  &  !:    "           " 
    69       &     ppa1  = pp_to_be_computed ,  &  !:    "           " 
    70       ! 
    71       &     ppkth =  23.563_wp        ,  &  !: (non dimensional): gives the approximate 
    72       !                                     !: layer number above which  stretching will 
    73       !                                     !: be maximum. Usually of order jpk/2. 
    74       &     ppacr =    9.00000000000_wp     !: (non dimensional): stretching factor 
    75       !                                     !: for the grid. The highest zacr, the smallest 
    76       !                                     !: the stretching. 
    7783 
    78    !! 
    79    !!  If both ppa0 ppa1 and ppsur are specified to 0, then 
    80    !!  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
    81    !! 
    82    REAL(wp), PARAMETER ::        & 
    83       &     ppdzmin = 6._wp           ,  &  !: (meters) vertical thickness of the top layer 
    84       &     pphmax  = 5720._wp              !: (meters) Maximum depth of the ocean gdepw(jpk) 
    85    !! 
     84   !!  Coefficients associated with the vertical coordinate system 
     85 
     86   REAL(wp), PARAMETER  ::                     & 
     87      &     ppsur =   pp_to_be_computed     ,  &  !: Computed in domzgr, set ppdzmin and pphmax below 
     88      &     ppa0  =   pp_to_be_computed     ,  &  !:    "           " 
     89      &     ppa1  =   pp_to_be_computed     ,  &  !:    "           " 
     90      &     ppkth =   23.563_wp             ,  &  !: (non dimensional): gives the approximate 
     91      !                                           !: layer number above which  stretching will 
     92      !                                           !: be maximum. Usually of order jpk/2. 
     93      &     ppacr =   9.00000000000_wp            !: (non dimensional): stretching factor 
     94      !                                           !: for the grid. The higher zacr, the smaller 
     95      !                                           !: the stretching. 
     96 
     97      !  If both ppa0 ppa1 and ppsur are specified to pp_to_be_computed, then 
     98      !  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
     99 
     100   REAL(wp), PARAMETER ::                      & 
     101      &     ppdzmin = 6._wp                 ,  &  !: (meters) vertical thickness of the top layer 
     102      &     pphmax  = 5720._wp                    !: (meters) Maximum depth of the ocean gdepw(jpk) 
    86103   LOGICAL,  PARAMETER ::                      & 
    87104      &     ldbletanh = .FALSE.                   !: Use/do not use double tanf function for vertical coordinates 
     
    90107      &     ppkth2  = pp_not_used           ,  &  !: 
    91108      &     ppacr2  = pp_not_used                 !: 
    92  
    93109   !!--------------------------------------------------------------------- 
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/par_EEL_R2.h90

    r2715 r4229  
    88   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    99   !!---------------------------------------------------------------------- 
    10    CHARACTER (len=16)      & 
     10   CHARACTER (len=16)         & 
    1111#if !defined key_agrif 
    12       , PARAMETER  & 
     12      , PARAMETER             & 
    1313#endif 
    14       ::     
    15       cp_cfg = "eel"            !: name of the configuration 
    16    INTEGER     & 
     14      ::                       
     15      cp_cfg  =  "eel"           !: Name of the configuration 
     16   INTEGER                    & 
    1717#if !defined key_agrif 
    18       , PARAMETER  & 
     18      , PARAMETER             & 
    1919#endif 
    20       :: & 
    21       jp_cfg = 2   ,         &  !: resolution of the configuration (km) 
     20      ::                      & 
     21      jp_cfg  =  2     ,      &  !: Resolution of the configuration (km) 
    2222 
    23       ! data size              !!! * size of all the input files * 
    24       jpidta  = 83,          &  !: 1st horizontal dimension ( >= jpi ) 
    25       jpjdta  = 242,         &  !: 2nd    "            "    ( >= jpj ) 
    26       jpkdta  = 30,          &  !: number of levels         ( >= jpk ) 
     23      ! Data domain size         !!! *  Size of all input files * 
     24      jpidta  =  83    ,      &  !: 1st lateral dimension ( >= jpiglo ) 
     25      jpjdta  =  242   ,      &  !: 2nd lateral dimension ( >= jpjglo ) 
     26      jpkdta  =  30    ,      &  !: Number of levels      ( >= jpk    ) 
    2727 
    28       ! global domain size     !!! * full domain * 
    29       jpiglo  = jpidta,      &  !: 1st dimension of global domain --> i 
    30       jpjglo  = jpjdta,      &  !: 2nd    "                  "    --> j 
    31       ! zoom starting position 
    32       jpizoom =   1   ,      &  !: left bottom (i,j) indices of the zoom 
    33       jpjzoom =   1   ,      &  !: in data indices 
     28#if defined key_c1d 
     29      ! Zoom domain size         !!! *  C1D zoom  * 
     30      jpiglo  =  3     ,      &  !: 1st dimension of global domain --> i 
     31      jpjglo  =  3     ,      &  !: 2nd dimension of global domain --> j 
     32      ! Domain characteristics 
     33      jperio  =  0               !: Lateral cond. type (between 0 and 6) 
    3434 
     35   INTEGER                    & 
     36      ::                      & 
     37      ! Starting position of the zoom 
     38      jpizoom =  1     ,      &  !: Left bottom (i,j) indices of the zoom 
     39      jpjzoom =  1               !: in data domain indices 
     40#else 
     41      ! Global domain size       !!! *  Global domain  * 
     42      jpiglo  =  jpidta,      &  !: 1st dimension of global domain --> i 
     43      jpjglo  =  jpjdta,      &  !: 2nd dimension of global domain --> j 
     44      ! Starting position of the zoom 
     45      jpizoom =  1     ,      &  !: Left bottom (i,j) indices of the zoom 
     46      jpjzoom =  1     ,      &  !: in data domain indices 
    3547      ! Domain characteristics 
    36       jperio  =     1           !: lateral cond. type (between 0 and 6) 
     48      jperio  =  1               !: Lateral cond. type (between 0 and 6) 
     49#endif 
     50 
    3751 
    3852   !!  Values set to pp_not_used indicates that this parameter is not used in THIS config. 
    3953   !!  Values set to pp_to_be_computed  indicates that variables will be computed in domzgr 
    40    REAL(wp), PARAMETER ::   &  !: 
    41       pp_not_used       = 999999._wp  , & !: ??? 
    42       pp_to_be_computed =      0._wp      !: ??? 
    43    !! 
    44    !! Coefficients associated with the horizontal coordinate system (jphgr_msh /= 0 ) 
    45    !! 
    46    INTEGER,PARAMETER   ::    & !: 
    47       jphgr_msh = 3            !: type of horizontal mesh 
    48       !                        ! = 0 curvilinear coordinate on the sphere 
    49       !                        !     read in coordinate.nc file 
    50       !                        ! = 1 geographical mesh on the sphere 
    51       !                        !     with regular grid-spacing 
    52       !                        ! = 2 f-plane with regular grid-spacing 
    53       !                        ! = 3 beta-plane with regular grid-spacing 
    54       !                        ! = 4 Mercator grid with T/U point at the equator  with 
    55       !                        !     isotropic resolution (e1_deg) 
     54 
     55   REAL(wp), PARAMETER ::              & 
     56      pp_not_used       = 999999._wp , &  !: 
     57      pp_to_be_computed = 0._wp           !: 
     58 
     59 
     60   !! Coefficients associated with the horizontal coordinate system 
     61 
     62   INTEGER, PARAMETER  ::     & 
     63      jphgr_msh = 3              !: type of horizontal mesh 
     64      !                          !: = 0 curvilinear coordinate on the sphere 
     65      !                          !:     read in coordinate.nc file 
     66      !                          !: = 1 geographical mesh on the sphere 
     67      !                          !:     with regular grid-spacing 
     68      !                          !: = 2 f-plane with regular grid-spacing 
     69      !                          !: = 3 beta-plane with regular grid-spacing 
     70      !                          !: = 4 Mercator grid with T/U point at the equator  with 
     71      !                          !:     isotropic resolution (e1_deg) 
    5672 
    5773      !   ppglam0 , ppgphi0: coordinates of the lower leftmost T point of the grid. 
    5874      !   The mercator grid starts only approximately at gphi0 because 
    5975      !   of the constraint that the equator be a T point. 
    60    REAL(wp) ,PARAMETER ::     &  !: 
    61       ppglam0  =    0.0_wp,   &  !: longitude of first raw and column T-point (jphgr_msh = 1) 
    62       ppgphi0  =   35.0_wp,   &  !: latitude  of first raw and column T-point (jphgr_msh = 1) 
    63       !                          ! latitude for the Coriolis or Beta parameter (jphgr_msh = 2 or 3) 
    64       ppe1_deg = pp_not_used ,   &  !: zonal      grid-spacing (degrees) 
    65       ppe2_deg = pp_not_used ,   &  !: meridional grid-spacing (degrees) 
     76 
     77   REAL(wp), PARAMETER ::     & 
     78      ppglam0  = 0.0_wp     , &  !: longitude of first raw and column T-point   (jphgr_msh = 1) 
     79      ppgphi0  = 35.0_wp    , &  !: latitude  of first raw and column T-point   (jphgr_msh = 1) 
     80      !                          !: latitude for the Coriolis or Beta parameter (jphgr_msh = 2 or 3) 
     81      ppe1_deg = pp_not_used, &  !: zonal      grid-spacing (degrees) 
     82      ppe2_deg = pp_not_used, &  !: meridional grid-spacing (degrees) 
    6683      ! 
    67       ppe1_m   = 2000.0_wp &  !: zonal      grid-spacing (meters ) 
     84      ppe1_m   = 2000.0_wp  , &  !: zonal      grid-spacing (meters ) 
    6885      ppe2_m   = 2000.0_wp       !: meridional grid-spacing (meters ) 
    69    !! 
     86 
     87 
    7088   !!  Coefficients associated with the vertical coordinate system 
    71    !! 
    72    REAL(wp) & 
     89 
     90   REAL(wp)                                    & 
    7391#if !defined key_agrif 
    74       , PARAMETER  & 
     92      , PARAMETER                              & 
    7593#endif 
    76       ::     &  !: 
    77       &     ppsur = -2033.194295283385_wp   ,  &  !: Computed in domzgr 
    78       &     ppa0  =  155.8325369664153_wp   ,  &  !: 
    79       &     ppa1  =  146.3615918601890_wp   ,  &  !: 
    80       ! 
    81       &     ppkth =  17.28520372419791_wp   ,  &  !: (non dimensional): gives the approximate 
     94      ::                                       &    
     95      &     ppsur =   -2033.194295283385_wp ,  &  !: Computed in domzgr, set ppdzmin, pphmax below 
     96      &     ppa0  =   155.8325369664153_wp  ,  &  !: 
     97      &     ppa1  =   146.3615918601890_wp  ,  &  !: 
     98      &     ppkth =   17.28520372419791_wp  ,  &  !: (non dimensional): gives the approximate 
    8299      !                                           !: layer number above which  stretching will 
    83100      !                                           !: be maximum. Usually of order jpk/2. 
    84       &     ppacr =  5.000000000000000_wp         !: (non dimensional): stretching factor 
    85       !                                           !: for the grid. The highest zacr, the smallest 
     101      &     ppacr =   5.000000000000000_wp        !: (non dimensional): stretching factor 
     102      !                                           !: for the grid. The higher zacr, the smaller 
    86103      !                                           !: the stretching. 
    87104 
    88    !! 
    89    !!  If both ppa0 ppa1 and ppsur are specified to 0, then 
    90    !!  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
    91    !! 
    92    REAL(wp), PARAMETER ::        & 
     105      !  If both ppa0 ppa1 and ppsur are specified to pp_to_be_computed, then 
     106      !  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
     107 
     108   REAL(wp), PARAMETER ::                      & 
    93109      &     ppdzmin = pp_not_used           ,  &  !: (meters) vertical thickness of the top layer 
    94110      &     pphmax  = pp_not_used                 !: (meters) Maximum depth of the ocean gdepw(jpk) 
    95    LOGICAL,  PARAMETER ::        & 
     111   LOGICAL,  PARAMETER ::                      & 
    96112      &     ldbletanh = .FALSE.                   !: Use/do not use double tanf function for vertical coordinates 
    97    REAL(wp), PARAMETER ::        & 
     113   REAL(wp), PARAMETER ::                      & 
    98114      &     ppa2    = pp_not_used           ,  &  !: Double tanh function parameters 
    99115      &     ppkth2  = pp_not_used           ,  &  !: 
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/par_EEL_R5.h90

    r2715 r4229  
    88   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    99   !!---------------------------------------------------------------------- 
    10    CHARACTER (len=16)      & 
     10   CHARACTER (len=16)         & 
    1111#if !defined key_agrif 
    12       , PARAMETER  & 
     12      , PARAMETER             & 
    1313#endif 
    14       ::     
    15       cp_cfg = "eel"            !: name of the configuration 
    16    INTEGER     & 
     14      ::                       
     15      cp_cfg  =  "eel"           !: Name of the configuration 
     16   INTEGER                    & 
    1717#if !defined key_agrif 
    18       , PARAMETER  & 
     18      , PARAMETER             & 
    1919#endif 
    20       :: & 
    21       jp_cfg = 5      ,      &  !: resolution of the configuration (km) 
     20      ::                      & 
     21      jp_cfg  =  5     ,      &  !: Resolution of the configuration (km) 
    2222 
    23       ! data size              !!! * size of all the input files 
    24       jpidta  =  66   ,      &  !: first horizontal dimension > or = to jpi 
    25       jpjdta  =  66   ,      &  !: second                     > or = to jpj 
    26       jpkdta  =  31   ,      &  !: number of levels           > or = to jpk 
     23      ! Data domain size         !!! *  Size of all input files  * 
     24      jpidta  =  66    ,      &  !: 1st lateral dimension ( >= jpiglo ) 
     25      jpjdta  =  66    ,      &  !: 2nd lateral dimension ( >= jpjglo ) 
     26      jpkdta  =  31    ,      &  !: Number of levels      ( >= jpk    ) 
    2727 
    28       ! total domain size      !!! * full domain * 
    29       jpiglo  = jpidta,      &  !: first  dimension of global domain --> i 
    30       jpjglo  = jpjdta,      &  !: second dimension of global domain --> j 
    31       ! zoom starting position 
    32       jpizoom =   1   ,      &  !: left bottom (i,j) indices of the zoom 
    33       jpjzoom =   1   ,      &  !: in data indices 
     28#if defined key_c1d 
     29      ! Zoom domain size         !!! *  C1D zoom  * 
     30      jpiglo  =  3     ,      &  !: 1st dimension of global domain --> i 
     31      jpjglo  =  3     ,      &  !: 2nd dimension of global domain --> j 
     32      ! Domain characteristics 
     33      jperio  =  0               !: Lateral cond. type (between 0 and 6) 
    3434 
     35   INTEGER                    & 
     36      ::                      & 
     37      ! Starting position of the zoom 
     38      jpizoom =  1     ,      &  !: Left bottom (i,j) indices of the zoom 
     39      jpjzoom =  1               !: in data domain indices 
     40#else 
     41      ! Global domain size       !!! *  Global domain  * 
     42      jpiglo  =  jpidta,      &  !: 1st dimension of global domain --> i 
     43      jpjglo  =  jpjdta,      &  !: 2nd dimension of global domain --> j 
     44      ! Starting position of the zoom 
     45      jpizoom =  1     ,      &  !: Left bottom (i,j) indices of the zoom 
     46      jpjzoom =  1     ,      &  !: in data domain indices 
    3547      ! Domain characteristics 
    36       jperio  =   1             !: lateral cond. type (between 0 and 6) 
     48      jperio  =  1               !: Lateral cond. type (between 0 and 6) 
     49#endif 
     50 
    3751 
    3852   !!  Values set to pp_not_used indicates that this parameter is not used in THIS config. 
    3953   !!  Values set to pp_to_be_computed  indicates that variables will be computed in domzgr 
    40    REAL(wp), PARAMETER ::   &  !: 
    41       pp_not_used       = 999999._wp ,  &  !: 
    42       pp_to_be_computed =      0._wp       !: 
    4354 
    44    !! Coefficients associated with the horizontal coordinate system (jphgr_msh /= 0 ) 
     55   REAL(wp), PARAMETER ::              & 
     56      pp_not_used       = 999999._wp , &  !: 
     57      pp_to_be_computed = 0._wp           !: 
    4558 
    46    INTEGER,PARAMETER   ::    & !: 
    47       jphgr_msh = 2            !: type of horizontal mesh 
    48       !                        ! = 0 curvilinear coordinate on the sphere 
    49       !                        !     read in coordinate.nc file 
    50       !                        ! = 1 geographical mesh on the sphere 
    51       !                        !     with regular grid-spacing 
    52       !                        ! = 2 f-plane with regular grid-spacing 
    53       !                        ! = 3 beta-plane with regular grid-spacing 
    54       !                        ! = 4 Mercator grid with T/U point at the equator  with 
    55       !                        !     isotropic resolution (e1_deg) 
     59 
     60   !! Coefficients associated with the horizontal coordinate system 
     61 
     62   INTEGER, PARAMETER  ::     & 
     63      jphgr_msh = 2              !: type of horizontal mesh 
     64      !                          !: = 0 curvilinear coordinate on the sphere 
     65      !                          !:     read in coordinate.nc file 
     66      !                          !: = 1 geographical mesh on the sphere 
     67      !                          !:     with regular grid-spacing 
     68      !                          !: = 2 f-plane with regular grid-spacing 
     69      !                          !: = 3 beta-plane with regular grid-spacing 
     70      !                          !: = 4 Mercator grid with T/U point at the equator  with 
     71      !                          !:     isotropic resolution (e1_deg) 
    5672 
    5773      !   ppglam0 , ppgphi0: coordinates of the lower leftmost T point of the grid. 
    5874      !   The mercator grid starts only approximately at gphi0 because 
    5975      !   of the constraint that the equator be a T point. 
    60    REAL(wp) & 
     76 
     77   REAL(wp)                       & 
    6178#if !defined key_agrif 
    62       , PARAMETER  & 
     79      , PARAMETER                 & 
    6380#endif 
    64       ::     &  !: 
    65       ppglam0  =    0.0_wp,   &  !: longitude of first raw and column T-point (jphgr_msh = 1) 
    66       ppgphi0  = 43.436430714_wp,   &  !: latitude  of first raw and column T-point (jphgr_msh = 1) 
    67       !                          ! latitude for the Coriolis or Beta parameter (jphgr_msh = 2 or 3) 
    68       ppe1_deg = pp_not_used &  !: zonal      grid-spacing (degrees) 
    69       ppe2_deg = pp_not_used &  !: meridional grid-spacing (degrees) 
     81      ::                          & 
     82      ppglam0  = 0.0_wp         , &  !: longitude of first raw and column T-point  (jphgr_msh = 1) 
     83      ppgphi0  = 43.436430714_wp, &  !: latitude  of first raw and column T-point  (jphgr_msh = 1) 
     84      !                              !: latitude for the Coriolis or Beta parameter (jphgr_msh = 2 or 3) 
     85      ppe1_deg = pp_not_used    , &  !: zonal      grid-spacing (degrees) 
     86      ppe2_deg = pp_not_used    , &  !: meridional grid-spacing (degrees) 
    7087      ! 
    71       ppe1_m   = 8000.0_wp,   &  !: zonal      grid-spacing (meters) 
    72       ppe2_m   = 8000.0_wp       !: meridional grid-spacing (meters) 
    73    !! 
     88      ppe1_m   = 8000.0_wp      , &  !: zonal      grid-spacing (meters ) 
     89      ppe2_m   = 8000.0_wp           !: meridional grid-spacing (meters ) 
     90 
     91 
    7492   !!  Coefficients associated with the vertical coordinate system 
    75    !! 
    76    REAL(wp), PARAMETER  ::       &   !: 
    77       &     ppsur = -4762.96143546300_wp    ,  &  !: Computed in domzgr, set ppdzmin, pphmax below 
     93 
     94   REAL(wp), PARAMETER  ::                     & 
     95      &     ppsur =   -4762.96143546300_wp  ,  &  !: Computed in domzgr, set ppdzmin, pphmax below 
    7896      &     ppa0  =   255.58049070440_wp    ,  &  !: 
    7997      &     ppa1  =   245.58132232490_wp    ,  &  !: 
    80       ! 
    81       &     ppkth =    21.43336197938_wp    ,  &  !: (non dimensional): gives the approximate 
     98      &     ppkth =   21.43336197938_wp     ,  &  !: (non dimensional): gives the approximate 
    8299      !                                           !: layer number above which  stretching will 
    83100      !                                           !: be maximum. Usually of order jpk/2. 
    84       &     ppacr =     3.00000000000_wp          !: (non dimensional): stretching factor 
    85       !                                           !: for the grid. The highest zacr, the smallest 
     101      &     ppacr =   3.00000000000_wp            !: (non dimensional): stretching factor 
     102      !                                           !: for the grid. The higher zacr, the smaller 
    86103      !                                           !: the stretching. 
    87104 
    88    !! 
    89    !!  If both ppa0 ppa1 and ppsur are specified to 0, then 
    90    !!  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
    91    !! 
    92    REAL(wp), PARAMETER ::        &  !: 
     105      !  If both ppa0 ppa1 and ppsur are specified to pp_to_be_computed, then 
     106      !  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
     107 
     108   REAL(wp), PARAMETER ::                      & 
    93109      &     ppdzmin = pp_not_used           ,  &  !: (meters) vertical thickness of the top layer 
    94110      &     pphmax  = pp_not_used                 !: (meters) Maximum depth of the ocean gdepw(jpk) 
    95    LOGICAL,  PARAMETER ::        & 
     111   LOGICAL,  PARAMETER ::                      & 
    96112      &     ldbletanh = .FALSE.                   !: Use/do not use double tanf function for vertical coordinates 
    97    REAL(wp), PARAMETER ::        & 
     113   REAL(wp), PARAMETER ::                      & 
    98114      &     ppa2    = pp_not_used           ,  &  !: Double tanh function parameters 
    99115      &     ppkth2  = pp_not_used           ,  &  !: 
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/par_EEL_R6.h90

    r2715 r4229  
    88   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    99   !!---------------------------------------------------------------------- 
    10    CHARACTER (len=16)      & 
     10   CHARACTER (len=16)         & 
    1111#if !defined key_agrif 
    12       , PARAMETER  & 
     12      , PARAMETER             & 
    1313#endif 
    14       ::     
    15       cp_cfg = "eel"            !: name of the configuration 
    16    INTEGER     & 
     14      ::                       
     15      cp_cfg  =  "eel"           !: Name of the configuration 
     16   INTEGER                    & 
    1717#if !defined key_agrif 
    18       , PARAMETER  & 
     18      , PARAMETER             & 
    1919#endif 
    20       ::     & 
    21       jp_cfg = 6      ,      &  !: resolution of the configuration (km) 
     20      ::                      & 
     21      jp_cfg  =  6     ,      &  !: Resolution of the configuration (km) 
    2222 
    23       ! data size              !!! * size of all the input files * 
    24       jpidta  = 29,          &  !: 1st lateral dimension ( >= jpi ) 
    25       jpjdta  = 83,          &  !: 2nd    "         "    ( >= jpj ) 
    26       jpkdta  = 30,          &  !: number of levels      ( >= jpk ) 
     23      ! Data domain size         !!! *  Size of all input files * 
     24      jpidta  =  29    ,      &  !: 1st lateral dimension ( >= jpiglo ) 
     25      jpjdta  =  83    ,      &  !: 2nd lateral dimension ( >= jpjglo ) 
     26      jpkdta  =  30    ,      &  !: Number of levels      ( >= jpk    ) 
    2727 
    28       ! global domain size     !!! * full domain * 
    29       jpiglo  = jpidta,      &  !: 1st dimension of global domain --> i 
    30       jpjglo  = jpjdta,      &  !: 2nd    "                  "    --> j 
    31       ! starting position of the zoom 
    32       jpizoom =   1   ,      &  !: left bottom (i,j) indices of the zoom 
    33       jpjzoom =   1   ,      &  !: in data domain indices 
     28#if defined key_c1d 
     29      ! Zoom domain size         !!! *  C1D zoom  * 
     30      jpiglo  =  3     ,      &  !: 1st dimension of global domain --> i 
     31      jpjglo  =  3     ,      &  !: 2nd dimension of global domain --> j 
     32      ! Domain characteristics 
     33      jperio  =  0               !: Lateral cond. type (between 0 and 6) 
    3434 
     35   INTEGER                    & 
     36      ::                      & 
     37      ! Starting position of the zoom 
     38      jpizoom =  1     ,      &  !: Left bottom (i,j) indices of the zoom 
     39      jpjzoom =  1               !: in data domain indices 
     40#else 
     41      ! Global domain size       !!! *  Global domain  * 
     42      jpiglo  =  jpidta,      &  !: 1st dimension of global domain --> i 
     43      jpjglo  =  jpjdta,      &  !: 2nd dimension of global domain --> j 
     44      ! Starting position of the zoom 
     45      jpizoom =  1     ,      &  !: Left bottom (i,j) indices of the zoom 
     46      jpjzoom =  1     ,      &  !: in data domain indices 
    3547      ! Domain characteristics 
    36       jperio  =      1          !: lateral cond. type (between 0 and 6) 
     48      jperio  =  1               !: Lateral cond. type (between 0 and 6) 
     49#endif 
     50 
    3751 
    3852   !!  Values set to pp_not_used indicates that this parameter is not used in THIS config. 
    3953   !!  Values set to pp_to_be_computed  indicates that variables will be computed in domzgr 
    40    REAL(wp), PARAMETER ::   &  !: 
    41       pp_not_used       = 999999._wp ,  &  !: ??? 
    42       pp_to_be_computed =      0._wp       !: ??? 
    4354 
    44    !! Coefficients associated with the horizontal coordinate system (jphgr_msh /= 0 ) 
     55   REAL(wp), PARAMETER ::              & 
     56      pp_not_used       = 999999._wp , &  !: 
     57      pp_to_be_computed = 0._wp           !: 
    4558 
    46    INTEGER,PARAMETER   ::    & !: 
    47       jphgr_msh = 3            !: type of horizontal mesh 
    48       !                        ! = 0 curvilinear coordinate on the sphere 
    49       !                        !     read in coordinate.nc file 
    50       !                        ! = 1 geographical mesh on the sphere 
    51       !                        !     with regular grid-spacing 
    52       !                        ! = 2 f-plane with regular grid-spacing 
    53       !                        ! = 3 beta-plane with regular grid-spacing 
    54       !                        ! = 4 Mercator grid with T/U point at the equator  with 
    55       !                        !     isotropic resolution (e1_deg) 
     59 
     60   !! Coefficients associated with the horizontal coordinate system 
     61 
     62   INTEGER, PARAMETER  ::     & 
     63      jphgr_msh = 3              !: type of horizontal mesh 
     64      !                          !: = 0 curvilinear coordinate on the sphere 
     65      !                          !:     read in coordinate.nc file 
     66      !                          !: = 1 geographical mesh on the sphere 
     67      !                          !:     with regular grid-spacing 
     68      !                          !: = 2 f-plane with regular grid-spacing 
     69      !                          !: = 3 beta-plane with regular grid-spacing 
     70      !                          !: = 4 Mercator grid with T/U point at the equator  with 
     71      !                          !:     isotropic resolution (e1_deg) 
    5672 
    5773      !   ppglam0 , ppgphi0: coordinates of the lower leftmost T point of the grid. 
    5874      !   The mercator grid starts only approximately at gphi0 because 
    5975      !   of the constraint that the equator be a T point. 
    60    REAL(wp) & 
     76 
     77   REAL(wp)                   & 
    6178#if !defined key_agrif 
    62       , PARAMETER  & 
     79      , PARAMETER             & 
    6380#endif 
    64       ::     &  !: 
    65       ppglam0  =    0.0_wp,   &  !: longitude of first raw and column T-point (jphgr_msh = 1) 
    66       ppgphi0  =   35.0_wp,   &  !: latitude  of first raw and column T-point (jphgr_msh = 1) 
    67       !                          !  latitude for the Coriolis or Beta parameter (jphgr_msh = 2 or 3) 
    68       ppe1_deg = pp_not_used,   &  !: zonal      grid-spacing (degrees) 
    69       ppe2_deg = pp_not_used,   &  !: meridional grid-spacing (degrees) 
     81      ::                      & 
     82      ppglam0  = 0.0_wp     , &  !: longitude of first raw and column T-point  (jphgr_msh = 1) 
     83      ppgphi0  = 35.0_wp    , &  !: latitude  of first raw and column T-point  (jphgr_msh = 1) 
     84      !                          !: latitude for the Coriolis or Beta parameter (jphgr_msh = 2 or 3) 
     85      ppe1_deg = pp_not_used, &  !: zonal      grid-spacing (degrees) 
     86      ppe2_deg = pp_not_used, &  !: meridional grid-spacing (degrees) 
    7087      ! 
    71       ppe1_m   = 6000.0_wp &  !: zonal      grid-spacing (meters ) 
     88      ppe1_m   = 6000.0_wp  , &  !: zonal      grid-spacing (meters ) 
    7289      ppe2_m   = 6000.0_wp       !: meridional grid-spacing (meters ) 
     90 
    7391 
    7492   !!  Coefficients associated with the vertical coordinate system 
    7593 
    76    REAL(wp), PARAMETER  ::       &  !: 
    77       &     ppsur = -2033.194295283385_wp   ,  &  !: Computed in domzgr 
    78       &     ppa0  =  155.8325369664153_wp   ,  &  !: 
    79       &     ppa1  =  146.3615918601890_wp   ,  &  !: 
    80       ! 
    81       &     ppkth =  17.28520372419791_wp   ,  &  !: (non dimensional): gives the approximate 
     94   REAL(wp), PARAMETER  ::                     & 
     95      &     ppsur =   -2033.194295283385_wp ,  &  !: Computed in domzgr, set ppdzmin, pphmax below 
     96      &     ppa0  =   155.8325369664153_wp  ,  &  !: 
     97      &     ppa1  =   146.3615918601890_wp  ,  &  !: 
     98      &     ppkth =   17.28520372419791_wp  ,  &  !: (non dimensional): gives the approximate 
    8299      !                                           !: layer number above which  stretching will 
    83100      !                                           !: be maximum. Usually of order jpk/2. 
    84       &     ppacr =  5.000000000000000_wp         !: (non dimensional): stretching factor 
    85       !                                           !: for the grid. The highest zacr, the smallest 
     101      &     ppacr =   5.000000000000000_wp        !: (non dimensional): stretching factor 
     102      !                                           !: for the grid. The higher zacr, the smaller 
    86103      !                                           !: the stretching. 
    87104 
     105      !  If both ppa0 ppa1 and ppsur are specified to pp_to_be_computed, then 
     106      !  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
    88107 
    89    !!  If both ppa0 ppa1 and ppsur are specified to 0, then 
    90    !!  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
    91    !! 
    92    REAL(wp), PARAMETER ::        &  !: 
     108   REAL(wp), PARAMETER ::                      & 
    93109      &     ppdzmin = pp_not_used           ,  &  !: (meters) vertical thickness of the top layer 
    94110      &     pphmax  = pp_not_used                 !: (meters) Maximum depth of the ocean gdepw(jpk) 
    95    LOGICAL,  PARAMETER ::        & 
     111   LOGICAL,  PARAMETER ::                      & 
    96112      &     ldbletanh = .FALSE.                   !: Use/do not use double tanf function for vertical coordinates 
    97    REAL(wp), PARAMETER ::        & 
     113   REAL(wp), PARAMETER ::                      & 
    98114      &     ppa2    = pp_not_used           ,  &  !: Double tanh function parameters 
    99115      &     ppkth2  = pp_not_used           ,  &  !: 
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/par_GYRE.h90

    r2715 r4229  
    88   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    99   !!---------------------------------------------------------------------- 
    10    CHARACTER (len=16)      & 
     10   CHARACTER (len=16)         & 
    1111#if !defined key_agrif 
    12       , PARAMETER  & 
     12      , PARAMETER             & 
    1313#endif 
    14       ::     
    15       cp_cfg = "gyre"           !: name of the configuration 
    16    INTEGER     & 
     14      ::                       
     15      cp_cfg  =  "gyre"          !: Name of the configuration 
     16   INTEGER                    & 
    1717#if !defined key_agrif 
    18       , PARAMETER  & 
     18      , PARAMETER             & 
    1919#endif 
    20       :: & 
    21       jp_cfg =  1   ,        &  !:  
     20      ::                      & 
     21      jp_cfg  =  1     ,      &  !: Resolution of the configuration (degrees) 
    2222 
    23       ! data size              !!! * size of all the input files * 
    24       jpidta  = 30*jp_cfg+2, &  !: 1st horizontal dimension ( >= jpi ) 
    25       jpjdta  = 20*jp_cfg+2, &  !: 2nd    "            "    ( >= jpj ) 
    26       jpkdta  = 31,          &  !: number of levels         ( >= jpk ) 
     23      ! Data domain size         !!! *  Size of all input files * 
     24      jpidta  =  30*jp_cfg+2, &  !: 1st lateral dimension ( >= jpiglo ) 
     25      jpjdta  =  20*jp_cfg+2, &  !: 2nd lateral dimension ( >= jpjglo ) 
     26      jpkdta  =  31         , &  !: Number of levels      ( >= jpk    ) 
    2727 
    28       ! global domain size     !!! * full domain * 
    29       jpiglo  = jpidta,      &  !: 1st dimension of global domain --> i 
    30       jpjglo  = jpjdta,      &  !: 2nd    "                  "    --> j 
    31       ! zoom starting position 
    32       jpizoom =   1   ,      &  !: left bottom (i,j) indices of the zoom 
    33       jpjzoom =   1   ,      &  !: in data indices 
     28#if defined key_c1d 
     29      ! Zoom domain size         !!! *  C1D zoom  * 
     30      jpiglo  =  3     ,      &  !: 1st dimension of global domain --> i 
     31      jpjglo  =  3     ,      &  !: 2nd dimension of global domain --> j 
     32      ! Domain characteristics 
     33      jperio  =  0               !: Lateral cond. type (between 0 and 6) 
    3434 
     35   INTEGER                    & 
     36      ::                      & 
     37      ! Starting position of the zoom 
     38      jpizoom =  1     ,      &  !: Left bottom (i,j) indices of the zoom 
     39      jpjzoom =  1               !: in data domain indices 
     40#else 
     41      ! Global domain size       !!! *  Global domain  * 
     42      jpiglo  =  jpidta,      &  !: 1st dimension of global domain --> i 
     43      jpjglo  =  jpjdta,      &  !: 2nd dimension of global domain --> j 
     44      ! Starting position of the zoom 
     45      jpizoom =  1     ,      &  !: Left bottom (i,j) indices of the zoom 
     46      jpjzoom =  1     ,      &  !: in data domain indices 
    3547      ! Domain characteristics 
    36       jperio  =     0           !: lateral cond. type (between 0 and 6) 
     48      jperio  =  0               !: Lateral cond. type (between 0 and 6) 
     49#endif 
     50 
    3751 
    3852   !!  Values set to pp_not_used indicates that this parameter is not used in THIS config. 
    3953   !!  Values set to pp_to_be_computed  indicates that variables will be computed in domzgr 
    40    REAL(wp), PARAMETER ::   &  !: 
    41       pp_not_used       = 999999._wp  , & !: ??? 
    42       pp_to_be_computed =      0._wp      !: ??? 
    43    !! 
    44    !! Coefficients associated with the horizontal coordinate system (jphgr_msh /= 0 ) 
    45    !! 
    46    INTEGER,PARAMETER   ::    & !: 
    47       jphgr_msh = 5            !: type of horizontal mesh 
    48       !                        ! = 0 curvilinear coordinate on the sphere 
    49       !                        !     read in coordinate.nc file 
    50       !                        ! = 1 geographical mesh on the sphere 
    51       !                        !     with regular grid-spacing 
    52       !                        ! = 2 f-plane with regular grid-spacing 
    53       !                        ! = 3 beta-plane with regular grid-spacing 
    54       !                        ! = 4 Mercator grid with T/U point at the equator  with 
    55       !                        !     isotropic resolution (e1_deg) 
    56       !                        ! =5  beta-plane with regular grid-spacing and rotated domain (GYRE configuration) 
     54 
     55   REAL(wp), PARAMETER ::              & 
     56      pp_not_used       = 999999._wp , &  !: 
     57      pp_to_be_computed = 0._wp           !: 
     58 
     59 
     60   !! Coefficients associated with the horizontal coordinate system 
     61 
     62   INTEGER, PARAMETER  ::     & 
     63      jphgr_msh = 5              !: type of horizontal mesh 
     64      !                          !: = 0 curvilinear coordinate on the sphere 
     65      !                          !:     read in coordinate.nc file 
     66      !                          !: = 1 geographical mesh on the sphere 
     67      !                          !:     with regular grid-spacing 
     68      !                          !: = 2 f-plane with regular grid-spacing 
     69      !                          !: = 3 beta-plane with regular grid-spacing 
     70      !                          !: = 4 Mercator grid with T/U point at the equator  with 
     71      !                          !:     isotropic resolution (e1_deg) 
     72      !                          !: = 5 beta-plane with regular grid-spacing and rotated domain (GYRE configuration) 
    5773 
    5874      !   ppglam0 , ppgphi0: coordinates of the lower leftmost T point of the grid. 
    5975      !   The mercator grid starts only approximately at gphi0 because 
    6076      !   of the constraint that the equator be a T point. 
    61    REAL(wp) & 
     77 
     78   REAL(wp)                   & 
    6279#if !defined key_agrif 
    63       , PARAMETER  & 
     80      , PARAMETER             & 
    6481#endif 
    65       ::     &  !: 
    66       ppglam0  =    0.0_wp,   &  !: longitude of first raw and column T-point (jphgr_msh = 1) 
    67       ppgphi0  =   29.0_wp,   &  !: latitude  of first raw and column T-point (jphgr_msh = 1) 
    68       !                          ! latitude for the Coriolis or Beta parameter (jphgr_msh = 2 or 3) 
    69       ppe1_deg = pp_not_used ,  &  !: zonal      grid-spacing (degrees) 
    70       ppe2_deg = pp_not_used ,  &  !: meridional grid-spacing (degrees) 
     82      ::                      & 
     83      ppglam0  = 0.0_wp     , &  !: longitude of first raw and column T-point  (jphgr_msh = 1) 
     84      ppgphi0  = 29.0_wp    , &  !: latitude  of first raw and column T-point  (jphgr_msh = 1) 
     85      !                          !: latitude for the Coriolis or Beta parameter (jphgr_msh = 2 or 3) 
     86      ppe1_deg = pp_not_used, &  !: zonal      grid-spacing (degrees) 
     87      ppe2_deg = pp_not_used, &  !: meridional grid-spacing (degrees) 
    7188      ! 
    72       ppe1_m   = pp_not_used,    &  !: zonal      grid-spacing (meters ) 
    73       ppe2_m   = pp_not_used        !: meridional grid-spacing (meters ) 
    74    !! 
     89      ppe1_m   = pp_not_used, &  !: zonal      grid-spacing (meters ) 
     90      ppe2_m   = pp_not_used     !: meridional grid-spacing (meters ) 
     91 
     92 
    7593   !!  Coefficients associated with the vertical coordinate system 
    76    !! 
    7794 
    78    REAL(wp), PARAMETER  ::       &  !: 
    79       &     ppsur = -2033.194295283385_wp   ,  &  !:  
    80       &     ppa0  =  155.8325369664153_wp   ,  &  !: 
    81       &     ppa1  =  146.3615918601890_wp   ,  &  !: 
    82       ! 
    83       &     ppkth =  17.28520372419791_wp   ,  &  !: (non dimensional): gives the approximate 
    84       !                                           !    layer number above which  stretching will 
    85       !                                           !    be maximum. Usually of order jpk/2. 
    86       &     ppacr =  5.000000000000000_wp         !: (non dimensional): stretching factor 
    87       !                                           !    for the grid. The highest zacr, the smallest 
    88       !                                           !    the stretching. 
     95   REAL(wp), PARAMETER  ::                     & 
     96      &     ppsur =   -2033.194295283385_wp ,  &  !: 
     97      &     ppa0  =   155.8325369664153_wp  ,  &  !: 
     98      &     ppa1  =   146.3615918601890_wp  ,  &  !: 
     99      &     ppkth =   17.28520372419791_wp  ,  &  !: (non dimensional): gives the approximate 
     100      !                                           !: layer number above which  stretching will 
     101      !                                           !: be maximum. Usually of order jpk/2. 
     102      &     ppacr =   5.000000000000000_wp        !: (non dimensional): stretching factor 
     103      !                                           !: for the grid. The higher zacr, the smaller 
     104      !                                           !: the stretching. 
    89105 
    90    !! 
    91    !!  If all ppa0 ppa1 and ppsur are specified to 0, then 
    92    !!  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
    93    !! 
    94    REAL(wp), PARAMETER ::        &  !: 
    95       &     ppdzmin = pp_not_used   ,  &  !: (meters): depth of the top (first) model layer 
    96       !                             !            depth of second "w" level 
    97       &     pphmax  = pp_not_used         !: (meters): maximum depth of the ocean 
    98       !                             !            depth of the last "w" level 
    99    LOGICAL,  PARAMETER ::        & 
     106      !  If both ppa0 ppa1 and ppsur are specified to pp_to_be_computed, then 
     107      !  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
     108 
     109   REAL(wp), PARAMETER ::                      & 
     110      &     ppdzmin = pp_not_used           ,  &  !: (meters) vertical thickness of the top layer 
     111      &     pphmax  = pp_not_used                 !: (meters) Maximum depth of the ocean gdepw(jpk) 
     112   LOGICAL,  PARAMETER ::                      & 
    100113      &     ldbletanh = .FALSE.                   !: Use/do not use double tanf function for vertical coordinates 
    101    REAL(wp), PARAMETER ::        & 
     114   REAL(wp), PARAMETER ::                      & 
    102115      &     ppa2    = pp_not_used           ,  &  !: Double tanh function parameters 
    103116      &     ppkth2  = pp_not_used           ,  &  !: 
    104117      &     ppacr2  = pp_not_used                 !: 
    105  
    106118   !!--------------------------------------------------------------------- 
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/par_ORCA_R025.h90

    r2715 r4229  
    99   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    1010   !!---------------------------------------------------------------------- 
    11    CHARACTER (len=16)      & 
     11   CHARACTER (len=16)         & 
    1212#if !defined key_agrif 
    13       , PARAMETER  & 
     13      , PARAMETER             & 
    1414#endif 
    15       ::     
    16       cp_cfg = "orca"           !: name of the configuration 
    17    INTEGER     & 
     15      ::                       
     16      cp_cfg  =  "orca"          !: Name of the configuration 
     17   INTEGER                    & 
    1818#if !defined key_agrif 
    19       , PARAMETER  & 
     19      , PARAMETER             & 
    2020#endif 
    21       :: & 
    22       jp_cfg = 025  ,        &  !: resolution of the configuration (degrees) 
    23       ! Original data size 
    24       jpidta  = 1442,        &  !: first horizontal dimension > or = to jpi 
    25       jpjdta  = 1021,        &  !: second                     > or = to jpj 
     21      ::                      & 
     22      jp_cfg  =  025   ,      &  !: Resolution of the configuration (degrees) 
     23 
     24      ! Data domain size         !!! *  Size of all input files  * 
     25      jpidta  =  1442  ,      &  !: 1st lateral dimension ( >= jpiglo ) 
     26      jpjdta  =  1021  ,      &  !: 2nd lateral dimension ( >= jpjglo ) 
    2627#if key_orca_r025==75 
    27       jpkdta  = 75 ,         &  !: number of levels           > or = to jpk 
     28      jpkdta  =  75    ,      &  !: Number of levels      ( >= jpk    ) 
    2829#else 
    29       jpkdta  = 46 ,         &  !: number of levels           > or = to jpk 
     30      jpkdta  =  46    ,      &  !: Number of levels      ( >= jpk    ) 
    3031#endif 
    31       ! total domain matrix size 
    32       jpiglo  = jpidta,      &  !: first  dimension of global domain --> i 
    33       jpjglo  = jpjdta,      &  !: second dimension of global domain --> j 
    34       ! starting position of the zoom 
    35       jpizoom =   1   ,      &  !: left bottom (i,j) indices of the zoom 
    36       jpjzoom =   1   ,      &  !: in data indices 
     32 
     33#if defined key_c1d 
     34      ! Zoom domain size         !!! *  C1D zoom  * 
     35      jpiglo  =  3     ,      &  !: 1st dimension of global domain --> i 
     36      jpjglo  =  3     ,      &  !: 2nd dimension of global domain --> j 
    3737      ! Domain characteristics 
    38       jperio  =    4            !: lateral cond. type (between 0 and 6) 
     38      jperio  =  0               !: Lateral cond. type (between 0 and 6) 
     39 
     40   INTEGER                    & 
     41      ::                      & 
     42      ! Starting position of the zoom 
     43      jpizoom =  1     ,      &  !: Left bottom (i,j) indices of the zoom 
     44      jpjzoom =  1               !: in data domain indices 
     45#else 
     46      ! Global domain size       !!! *  Global domain  * 
     47      jpiglo  =  jpidta,      &  !: 1st dimension of global domain --> i 
     48      jpjglo  =  jpjdta,      &  !: 2nd dimension of global domain --> j 
     49      ! Starting position of the zoom 
     50      jpizoom =  1     ,      &  !: Left bottom (i,j) indices of the zoom 
     51      jpjzoom =  1     ,      &  !: in data domain indices 
     52      ! Domain characteristics 
     53      jperio  =  4               !: Lateral cond. type (between 0 and 6) 
     54#endif 
     55 
    3956 
    4057   !!  Values set to pp_not_used indicates that this parameter is not used in THIS config. 
    4158   !!  Values set to pp_to_be_computed  indicates that variables will be computed in domzgr 
    42    REAL,PARAMETER      ::  pp_not_used = 999999_wp , & 
    43       &                    pp_to_be_computed = 0._wp 
    44    !! 
    45    !! Coefficients associated with the horizontal coordinate system (jphgr_msh /= 0 ) 
    46    !! 
    47    INTEGER, PARAMETER ::     & ! 
    48       jphgr_msh = 0            !: type of horizontal mesh 
    49       !                        !  = 0 curvilinear coordinate on the sphere 
    50       !                        !      read in coordinate.nc file 
    51       !                        !  = 1 geographical mesh on the sphere 
    52       !                        !      with regular grid-spacing 
    53       !                        !  = 2 f-plane with regular grid-spacing 
    54       !                        !  = 3 beta-plane with regular grid-spacing 
    55       !                        !  = 4 Mercator grid with T/U point at the equator  with 
    56       !                        !      isotropic resolution (e1_deg) 
     59 
     60   REAL(wp), PARAMETER ::              & 
     61      pp_not_used       = 999999._wp , &  !: 
     62      pp_to_be_computed = 0._wp           !: 
     63 
     64 
     65   !! Coefficients associated with the horizontal coordinate system 
     66 
     67   INTEGER, PARAMETER  ::     & 
     68      jphgr_msh = 0              !: type of horizontal mesh 
     69      !                          !: = 0 curvilinear coordinate on the sphere 
     70      !                          !:     read in coordinate.nc file 
     71      !                          !: = 1 geographical mesh on the sphere 
     72      !                          !:     with regular grid-spacing 
     73      !                          !: = 2 f-plane with regular grid-spacing 
     74      !                          !: = 3 beta-plane with regular grid-spacing 
     75      !                          !: = 4 Mercator grid with T/U point at the equator  with 
     76      !                          !:     isotropic resolution (e1_deg) 
    5777 
    5878      !   ppglam0 , ppgphi0: coordinates of the lower leftmost T point of the grid. 
    5979      !   The mercator grid starts only approximately at gphi0 because 
    6080      !   of the constraint that the equator be a T point. 
    61    REAL(wp), PARAMETER ::       &  ! 
    62       ppglam0  = pp_not_used,   &  !: longitude of first raw and column T-point (jphgr_msh = 1) 
    63       ppgphi0  = pp_not_used,   &  !: latitude  of first raw and column T-point (jphgr_msh = 1) 
    64       !                            !  latitude for the Coriolis or Beta parameter (jphgr_msh = 2 or 3) 
    65       ppe1_deg = pp_not_used,   &  !: zonal      grid-spacing (degrees) 
    66       ppe2_deg = pp_not_used,   &  !: meridional grid-spacing (degrees) 
     81 
     82   REAL(wp), PARAMETER ::     & 
     83      ppglam0  = pp_not_used, &  !: longitude of first raw and column T-point   (jphgr_msh = 1) 
     84      ppgphi0  = pp_not_used, &  !: latitude  of first raw and column T-point   (jphgr_msh = 1) 
     85      !                          !: latitude for the Coriolis or Beta parameter (jphgr_msh = 2 or 3) 
     86      ppe1_deg = pp_not_used, &  !: zonal      grid-spacing (degrees) 
     87      ppe2_deg = pp_not_used, &  !: meridional grid-spacing (degrees) 
    6788      ! 
    68       ppe1_m   = pp_not_used,   &  !: zonal      grid-spacing (meters ) 
    69       ppe2_m   = pp_not_used       !: meridional grid-spacing (meters ) 
     89      ppe1_m   = pp_not_used, &  !: zonal      grid-spacing (meters ) 
     90      ppe2_m   = pp_not_used     !: meridional grid-spacing (meters ) 
     91 
    7092 
    7193   !!  Coefficients associated with the vertical coordinate system 
    7294 
    7395#if key_orca_r025==75 
    74    REAL(wp), PARAMETER  ::       & 
    75       &     ppsur =  -3958.951371276829_wp ,  &  !: ORCA r025 coefficients 
     96   REAL(wp), PARAMETER  ::                     & 
     97      &     ppsur =   -3958.951371276829_wp ,  &  !: ORCA r025 coefficients 
    7698      &     ppa0  =   103.9530096000000_wp  ,  &  !: (75 levels case) 
    7799      &     ppa1  =   2.415951269000000_wp  ,  &  !: 
     
    79101      !                                           !: layer number above which  stretching will 
    80102      !                                           !: be maximum. Usually of order jpk/2. 
    81       &     ppacr =       7.00000000000_wp        !: (non dimensional): stretching factor 
     103      &     ppacr =   7.00000000000_wp            !: (non dimensional): stretching factor 
    82104      !                                           !: for the grid. The higher zacr, the smaller 
    83105      !                                           !: the stretching. 
    84    !! 
    85    !!  If both ppa0 ppa1 and ppsur are specified to pp_to_be_computed, then 
    86    !!  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
    87    !! 
     106 
     107      !  If both ppa0 ppa1 and ppsur are specified to pp_to_be_computed, then 
     108      !  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
     109 
    88110   REAL(wp), PARAMETER ::                      & 
    89111      &     ppdzmin = pp_not_used           ,  &  !: (meters) vertical thickness of the top layer 
    90112      &     pphmax  = pp_not_used                 !: (meters) Maximum depth of the ocean gdepw(jpk) 
    91    !! 
    92113   LOGICAL,  PARAMETER ::                      & 
    93114      &     ldbletanh = .TRUE.                    !: Use/do not use double tanf function for vertical coordinates 
    94115   REAL(wp), PARAMETER ::                      & 
    95       &     ppa2  =   100.7609285000000_wp  ,  &  !: Double tanh function parameters 
    96       &     ppkth2=   48.02989372000000_wp  ,  &  !: 
    97       &     ppacr2=    13.00000000000_wp          !: 
    98       ! 
     116      &     ppa2    = 100.7609285000000_wp  ,  &  !: Double tanh function parameters 
     117      &     ppkth2  = 48.02989372000000_wp  ,  &  !: 
     118      &     ppacr2  = 13.00000000000_wp           !: 
    99119#else 
    100    REAL(wp), PARAMETER  ::       & 
    101       &     ppsur = pp_to_be_computed ,        &  !: Computed in domzgr, set ppdzmin and pphmax below 
    102       &     ppa0  = pp_to_be_computed ,        &  !:    "           " 
    103       &     ppa1  = pp_to_be_computed ,        &  !:    "           " 
    104       ! 
    105       &     ppkth =  23.563_wp        ,        &  !: (non dimensional): gives the approximate 
     120   REAL(wp), PARAMETER  ::                     & 
     121      &     ppsur =   pp_to_be_computed     ,  &  !: Computed in domzgr, set ppdzmin and pphmax below 
     122      &     ppa0  =   pp_to_be_computed     ,  &  !:    "           " 
     123      &     ppa1  =   pp_to_be_computed     ,  &  !:    "           " 
     124      &     ppkth =   23.563_wp             ,  &  !: (non dimensional): gives the approximate 
    106125      !                                           !: layer number above which  stretching will 
    107126      !                                           !: be maximum. Usually of order jpk/2. 
    108127      &     ppacr =   9.00000000000_wp            !: (non dimensional): stretching factor 
    109       !                                           !: for the grid. The highest zacr, the smallest 
     128      !                                           !: for the grid. The higher zacr, the smaller 
    110129      !                                           !: the stretching. 
    111    !! 
    112    !!  If both ppa0 ppa1 and ppsur are specified to pp_to_be_computed, then 
    113    !!  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
    114    !! 
     130 
     131      !  If both ppa0 ppa1 and ppsur are specified to pp_to_be_computed, then 
     132      !  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
     133 
    115134   REAL(wp), PARAMETER ::                      & 
    116       &     ppdzmin = 6._wp           ,        &  !: (meters) vertical thickness of the top layer 
     135      &     ppdzmin = 6._wp                 ,  &  !: (meters) vertical thickness of the top layer 
    117136      &     pphmax  = 5750._wp                    !: (meters) Maximum depth of the ocean gdepw(jpk) 
    118    !! 
    119137   LOGICAL,  PARAMETER ::                      & 
    120138      &     ldbletanh = .FALSE.                   !: Use/do not use double tanf function for vertical coordinates 
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/par_ORCA_R05.h90

    r2715 r4229  
    99   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    1010   !!---------------------------------------------------------------------- 
    11    CHARACTER (len=16)      & 
     11   CHARACTER (len=16)         & 
    1212#if !defined key_agrif 
    13       , PARAMETER  & 
     13      , PARAMETER             & 
    1414#endif 
    15       ::     
    16       cp_cfg = "orca"           !: name of the configuration 
    17    INTEGER     & 
     15      ::                       
     16      cp_cfg  =  "orca"          !: Name of the configuration 
     17   INTEGER                    & 
    1818#if !defined key_agrif 
    19       , PARAMETER  & 
     19      , PARAMETER             & 
    2020#endif 
    21       :: & 
    22       jp_cfg = 05  ,         &  !: resolution of the configuration (degrees) 
     21      ::                      & 
     22      jp_cfg  =  05    ,      &  !: Resolution of the configuration (degrees) 
    2323 
    24       ! data size              !!! * size of all the input files * 
    25       jpidta  = 722,         &  !: 1st lateral dimension > or = to jpiglo 
    26       jpjdta  = 511,         &  !: 2nd   "         "     > or = to jpjglo 
    27       jpkdta  =  31             !: number of levels      > or = to jpkglo 
     24      ! Data domain size         !!! *  Size of all input files * 
     25      jpidta  =  722   ,      &  !: 1st lateral dimension ( >= jpiglo ) 
     26      jpjdta  =  511   ,      &  !: 2nd lateral dimension ( >= jpjglo ) 
     27      jpkdta  =  31    ,      &  !: Number of levels      ( >= jpk    ) 
    2828 
    29 #if defined key_antarctic 
    30       ! zoom domain size       !!! *  antarctic zoom  *  
    31    INTEGER     & 
    32 #if !defined key_agrif 
    33       , PARAMETER  & 
     29#if defined key_c1d 
     30      ! Zoom domain size         !!! *  C1D zoom  * 
     31      jpiglo  =  3     ,      &  !: 1st dimension of global domain --> i 
     32      jpjglo  =  3     ,      &  !: 2nd dimension of global domain --> j 
     33      ! Domain characteristics 
     34      jperio  =  0               !: Lateral cond. type (between 0 and 6) 
     35 
     36   INTEGER                    & 
     37      ::                      & 
     38      ! Starting position of the zoom 
     39      jpizoom =  1     ,      &  !: Left bottom (i,j) indices of the zoom 
     40      jpjzoom =  1               !: in data domain indices 
     41#elif defined key_antarctic 
     42      ! Zoom domain size         !!! *  Antarctic zoom  *  
     43      jpiglo  =  jpidta,      &  !: 1st dimension of global domain --> i 
     44      jpjglo  =  187   ,      &  !: 2nd dimension of global domain --> j 
     45      ! Starting position of the zoom 
     46      jpizoom =  1     ,      &  !: Left bottom (i,j) indices of the zoom 
     47      jpjzoom =  1     ,      &  !: in data domain indices 
     48      ! Domain characteristics 
     49      jperio  =  1               !: Lateral cond. type (between 0 and 6) 
     50#elif defined key_arctic 
     51      ! Zoom domain size         !!! *  Arctic zoom  * 
     52      jpiglo  =  562   ,      &  !: 1st dimension of global domain --> i 
     53      jpjglo  =  jpjdta-301+1,&  !: 2nd dimension of global domain --> j 
     54      ! Starting position of the zoom 
     55      jpizoom =  81    ,      &  !: Left bottom (i,j) indices of the zoom 
     56      jpjzoom =  301   ,      &  !: in data domain indices 
     57      ! Domain characteristics 
     58      jperio  =  5               !: Lateral cond. type (between 0 and 6) 
     59#else 
     60      ! Global domain size       !!! *  Global domain  * 
     61      jpiglo  =  jpidta,      &  !: 1st dimension of global domain --> i 
     62      jpjglo  =  jpjdta,      &  !: 2nd dimension of global domain --> j 
     63      ! Starting position of the zoom 
     64      jpizoom =  1     ,      &  !: Left bottom (i,j) indices of the zoom 
     65      jpjzoom =  1     ,      &  !: in data domain indices 
     66      ! Domain characteristics 
     67      jperio  =  6               !: Lateral cond. type (between 0 and 6) 
    3468#endif 
    35       :: & 
    36       jpiglo  = jpidta,      &  !: 1st dimension of global domain --> i 
    37       jpjglo  = 187   ,      &  !: 2nd     "                 "    --> j  
    38       ! starting position of the zoom 
    39       jpizoom =   1   ,      &  !: left bottom (i,j) indices of the zoom 
    40       jpjzoom =   1   ,      &  !: in data domain indices 
    41       ! Domain characteristics 
    42       jperio  =   1             !: lateral cond. type (between 0 and 6) 
    4369 
    44 #elif defined key_arctic 
    45       ! zoom domain size       !!! *  arctic zoom  * 
    46    INTEGER    & 
    47 #if !defined key_agrif 
    48       , PARAMETER  & 
    49 #endif 
    50       :: & 
    51       ! zoom domain size       !!! *  arctic zoom  * 
    52       jpiglo  = 562,         &  !: 1st dimension of global domain --> i 
    53       jpjglo  = jpjdta-301+1,&  !: 2nd     "                 "    --> j 
    54       ! zoom starting position 
    55       jpizoom =  81   ,      &  !: left bottom (i,j) indices of the zoom 
    56       jpjzoom = 301   ,      &  !: in data domain indices 
    57       ! Domain characteristics 
    58       jperio  =   5             !: lateral cond. type (between 0 and 6) 
    59  
    60 #else 
    61       ! global domain size     !!! *  global domain  * 
    62    INTEGER    & 
    63 #if !defined key_agrif 
    64       , PARAMETER  & 
    65 #endif 
    66       :: & 
    67       jpiglo  = jpidta,      &  !: 1st dimension of global domain --> i 
    68       jpjglo  = jpjdta,      &  !: 2nd     "                 "    --> j 
    69       ! zoom starting position     
    70       jpizoom =   1   ,      &  !: left bottom (i,j) indices of the zoom 
    71       jpjzoom =   1   ,      &  !: in data domain indices 
    72       ! Domain characteristics 
    73       jperio  =    6            !: lateral cond. type (between 0 and 6) 
    74 #endif 
    7570 
    7671   !!  Values set to pp_not_used indicates that this parameter is not used in THIS config. 
    7772   !!  Values set to pp_to_be_computed  indicates that variables will be computed in domzgr 
    78    REAL(wp), PARAMETER ::   & 
     73 
     74   REAL(wp), PARAMETER ::              & 
    7975      pp_not_used       = 999999._wp , &  !: 
    80       pp_to_be_computed = 0._wp          !: 
     76      pp_to_be_computed = 0._wp           !: 
    8177 
    82    !! Coefficients associated with the horizontal coordinate system (jphgr_msh /= 0 ) 
    8378 
    84    INTEGER, PARAMETER   ::   & ! 
    85       jphgr_msh = 0            !: type of horizontal mesh 
    86       !                        !  = 0 curvilinear coordinate on the sphere 
    87       !                        !      read in coordinate.nc file 
    88       !                        !  = 1 geographical mesh on the sphere 
    89       !                        !      with regular grid-spacing 
    90       !                        !  = 2 f-plane with regular grid-spacing 
    91       !                        !  = 3 beta-plane with regular grid-spacing 
    92       !                        !  = 4 Mercator grid with T/U point at the equator  with 
    93       !                        !      isotropic resolution (e1_deg) 
     79   !! Coefficients associated with the horizontal coordinate system 
     80 
     81   INTEGER, PARAMETER  ::     & 
     82      jphgr_msh = 0              !: type of horizontal mesh 
     83      !                          !: = 0 curvilinear coordinate on the sphere 
     84      !                          !:     read in coordinate.nc file 
     85      !                          !: = 1 geographical mesh on the sphere 
     86      !                          !:     with regular grid-spacing 
     87      !                          !: = 2 f-plane with regular grid-spacing 
     88      !                          !: = 3 beta-plane with regular grid-spacing 
     89      !                          !: = 4 Mercator grid with T/U point at the equator  with 
     90      !                          !:     isotropic resolution (e1_deg) 
    9491 
    9592      !   ppglam0 , ppgphi0: coordinates of the lower leftmost T point of the grid. 
    9693      !   The mercator grid starts only approximately at gphi0 because 
    9794      !   of the constraint that the equator be a T point. 
    98    REAL(wp) , PARAMETER ::      &  ! 
    99       ppglam0  = pp_not_used,   &  !: longitude of first raw and column T-point (jphgr_msh = 1) 
    100       ppgphi0  = pp_not_used,   &  !: latitude  of first raw and column T-point (jphgr_msh = 1) 
    101       !                            ! latitude for the Coriolis or Beta parameter (jphgr_msh = 2 or 3) 
    102       ppe1_deg = pp_not_used,   &  !: zonal      grid-spacing (degrees) 
    103       ppe2_deg = pp_not_used,   &  !: meridional grid-spacing (degrees) 
     95 
     96   REAL(wp), PARAMETER ::     & 
     97      ppglam0  = pp_not_used, &  !: longitude of first raw and column T-point   (jphgr_msh = 1) 
     98      ppgphi0  = pp_not_used, &  !: latitude  of first raw and column T-point   (jphgr_msh = 1) 
     99      !                          !: latitude for the Coriolis or Beta parameter (jphgr_msh = 2 or 3) 
     100      ppe1_deg = pp_not_used, &  !: zonal      grid-spacing (degrees) 
     101      ppe2_deg = pp_not_used, &  !: meridional grid-spacing (degrees) 
    104102      ! 
    105       ppe1_m   = pp_not_used,   &  !: zonal      grid-spacing (meters ) 
    106       ppe2_m   = pp_not_used       !: meridional grid-spacing (meters ) 
     103      ppe1_m   = pp_not_used, &  !: zonal      grid-spacing (meters ) 
     104      ppe2_m   = pp_not_used     !: meridional grid-spacing (meters ) 
    107105 
    108    !! 
    109    !! Vertical grid parameter for domzgr 
    110    !! ===================================== 
    111    !! 
    112    REAL(wp), PARAMETER  ::       & 
    113       &     ppsur = -4762.96143546300_wp    ,  &  !: ORCA r4, r2 and r05 coefficients 
     106 
     107   !!  Coefficients associated with the vertical coordinate system 
     108 
     109   REAL(wp), PARAMETER  ::                     & 
     110      &     ppsur =   -4762.96143546300_wp  ,  &  !: ORCA r4, r2 and r05 coefficients 
    114111      &     ppa0  =   255.58049070440_wp    ,  &  !: (default coefficients) 
    115112      &     ppa1  =   245.58132232490_wp    ,  &  !: 
    116       &     ppkth =    21.43336197938_wp    ,  &  !: (non dimensional): gives the approximate 
     113      &     ppkth =   21.43336197938_wp     ,  &  !: (non dimensional): gives the approximate 
    117114      !                                           !: layer number above which  stretching will 
    118115      !                                           !: be maximum. Usually of order jpk/2. 
    119       &     ppacr =     3.00000000000_wp          !: (non dimensional): stretching factor 
    120       !                                           !: for the grid. The highest zacr, the smallest 
     116      &     ppacr =   3.00000000000_wp            !: (non dimensional): stretching factor 
     117      !                                           !: for the grid. The higher zacr, the smaller 
    121118      !                                           !: the stretching. 
    122119 
    123    !! 
    124    !!  If both ppa0 ppa1 and ppsur are specified to 0, then 
    125    !!  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
    126    !! 
    127    REAL(wp), PARAMETER ::        & 
     120      !  If both ppa0 ppa1 and ppsur are specified to pp_to_be_computed, then 
     121      !  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
     122 
     123   REAL(wp), PARAMETER ::                      & 
    128124      &     ppdzmin = pp_not_used           ,  &  !: (meters) vertical thickness of the top layer 
    129125      &     pphmax  = pp_not_used                 !: (meters) Maximum depth of the ocean gdepw(jpk) 
    130    LOGICAL,  PARAMETER ::        & 
     126   LOGICAL,  PARAMETER ::                      & 
    131127      &     ldbletanh = .FALSE.                   !: Use/do not use double tanf function for vertical coordinates 
    132    REAL(wp), PARAMETER ::        & 
     128   REAL(wp), PARAMETER ::                      & 
    133129      &     ppa2    = pp_not_used           ,  &  !: Double tanh function parameters 
    134130      &     ppkth2  = pp_not_used           ,  &  !: 
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/par_ORCA_R1.h90

    r2715 r4229  
    1212   !! Use: key_orca_r1=75 to set 75 levels 
    1313   !!---------------------------------------------------------------------- 
    14    CHARACTER (len=16)      & 
     14   CHARACTER (len=16)         & 
    1515#if !defined key_agrif 
    16       , PARAMETER  & 
     16      , PARAMETER             & 
    1717#endif 
    18       ::     
    19       cp_cfg = "orca"           !: name of the configuration 
    20    INTEGER     & 
     18      ::                       
     19      cp_cfg  =  "orca"          !: Name of the configuration 
     20   INTEGER                    & 
    2121#if !defined key_agrif 
    22       , PARAMETER  & 
     22      , PARAMETER             & 
    2323#endif 
    24       :: & 
    25       jp_cfg = 1    ,        &  !: resolution of the configuration (degrees) 
    26       ! Original data size 
    27       jpidta  =  362,        &  !: first horizontal dimension > or = to jpi 
    28       jpjdta  =  292,        &  !: second                     > or = to jpj 
     24      ::                      & 
     25      jp_cfg  =  1     ,      &  !: Resolution of the configuration (degrees) 
     26 
     27      ! Data domain size         !!! *  Size of all input files  * 
     28      jpidta  =  362   ,      &  !: 1st lateral dimension ( >= jpiglo ) 
     29      jpjdta  =  292   ,      &  !: 2nd lateral dimension ( >= jpjglo ) 
    2930#if key_orca_r1==75 
    30       jpkdta  = 75 ,         &  !: number of levels           > or = to jpk 
     31      jpkdta  =  75    ,      &  !: Number of levels      ( >= jpk    ) 
    3132#else 
    32       jpkdta  = 46 ,         &  !: number of levels           > or = to jpk 
     33      jpkdta  =  46    ,      &  !: Number of levels      ( >= jpk    ) 
    3334#endif 
    34       ! total domain matrix size 
    35       jpiglo  = jpidta,      &  !: first  dimension of global domain --> i 
    36       jpjglo  = jpjdta,      &  !: second dimension of global domain --> j 
    37       ! starting position of the zoom 
    38       jpizoom =   1   ,      &  !: left bottom (i,j) indices of the zoom 
    39       jpjzoom =   1   ,      &  !: in data indices 
     35 
     36#if defined key_c1d 
     37      ! Zoom domain size         !!! *  C1D zoom  * 
     38      jpiglo  =  3     ,      &  !: 1st dimension of global domain --> i 
     39      jpjglo  =  3     ,      &  !: 2nd dimension of global domain --> j 
    4040      ! Domain characteristics 
    41       jperio  =   6             !: lateral cond. type (between 0 and 6) 
     41      jperio  =  0               !: Lateral cond. type (between 0 and 6) 
     42 
     43   INTEGER                    & 
     44      ::                      & 
     45      ! Starting position of the zoom 
     46      jpizoom =  1     ,      &  !: Left bottom (i,j) indices of the zoom 
     47      jpjzoom =  1               !: in data domain indices 
     48#else 
     49      ! Global domain size       !!! *  Global domain  * 
     50      jpiglo  =  jpidta,      &  !: 1st dimension of global domain --> i 
     51      jpjglo  =  jpjdta,      &  !: 2nd dimension of global domain --> j 
     52      ! Starting position of the zoom 
     53      jpizoom =  1     ,      &  !: Left bottom (i,j) indices of the zoom 
     54      jpjzoom =  1     ,      &  !: in data domain indices 
     55      ! Domain characteristics 
     56      jperio  =  6               !: Lateral cond. type (between 0 and 6) 
     57#endif 
     58 
    4259 
    4360   !!  Values set to pp_not_used indicates that this parameter is not used in THIS config. 
    4461   !!  Values set to pp_to_be_computed  indicates that variables will be computed in domzgr 
    45    REAL,PARAMETER      ::  pp_not_used = 999999_wp , & 
    46       &                    pp_to_be_computed = 0._wp 
    47    !! 
    48    !! Coefficients associated with the horizontal coordinate system (jphgr_msh /= 0 ) 
    49    !! 
    50    INTEGER, PARAMETER ::     & ! 
    51       jphgr_msh = 0            !: type of horizontal mesh 
    52       !                        !  = 0 curvilinear coordinate on the sphere 
    53       !                        !      read in coordinate.nc file 
    54       !                        !  = 1 geographical mesh on the sphere 
    55       !                        !      with regular grid-spacing 
    56       !                        !  = 2 f-plane with regular grid-spacing 
    57       !                        !  = 3 beta-plane with regular grid-spacing 
    58       !                        !  = 4 Mercator grid with T/U point at the equator  with 
    59       !                        !      isotropic resolution (e1_deg) 
     62 
     63   REAL(wp), PARAMETER ::              & 
     64      pp_not_used       = 999999._wp , &  !: 
     65      pp_to_be_computed = 0._wp           !: 
     66 
     67 
     68   !! Coefficients associated with the horizontal coordinate system 
     69 
     70   INTEGER, PARAMETER  ::     & 
     71      jphgr_msh = 0              !: type of horizontal mesh 
     72      !                          !: = 0 curvilinear coordinate on the sphere 
     73      !                          !:     read in coordinate.nc file 
     74      !                          !: = 1 geographical mesh on the sphere 
     75      !                          !:     with regular grid-spacing 
     76      !                          !: = 2 f-plane with regular grid-spacing 
     77      !                          !: = 3 beta-plane with regular grid-spacing 
     78      !                          !: = 4 Mercator grid with T/U point at the equator  with 
     79      !                          !:     isotropic resolution (e1_deg) 
    6080 
    6181      !   ppglam0 , ppgphi0: coordinates of the lower leftmost T point of the grid. 
    6282      !   The mercator grid starts only approximately at gphi0 because 
    6383      !   of the constraint that the equator be a T point. 
    64    REAL(wp), PARAMETER ::       &  ! 
    65       ppglam0  = pp_not_used,   &  !: longitude of first raw and column T-point (jphgr_msh = 1) 
    66       ppgphi0  = pp_not_used,   &  !: latitude  of first raw and column T-point (jphgr_msh = 1) 
    67       !                            !  latitude for the Coriolis or Beta parameter (jphgr_msh = 2 or 3) 
    68       ppe1_deg = pp_not_used,   &  !: zonal      grid-spacing (degrees) 
    69       ppe2_deg = pp_not_used,   &  !: meridional grid-spacing (degrees) 
     84 
     85   REAL(wp), PARAMETER ::     & 
     86      ppglam0  = pp_not_used, &  !: longitude of first raw and column T-point   (jphgr_msh = 1) 
     87      ppgphi0  = pp_not_used, &  !: latitude  of first raw and column T-point   (jphgr_msh = 1) 
     88      !                          !: latitude for the Coriolis or Beta parameter (jphgr_msh = 2 or 3) 
     89      ppe1_deg = pp_not_used, &  !: zonal      grid-spacing (degrees) 
     90      ppe2_deg = pp_not_used, &  !: meridional grid-spacing (degrees) 
    7091      ! 
    71       ppe1_m   = pp_not_used,   &  !: zonal      grid-spacing (meters ) 
    72       ppe2_m   = pp_not_used       !: meridional grid-spacing (meters ) 
     92      ppe1_m   = pp_not_used, &  !: zonal      grid-spacing (meters ) 
     93      ppe2_m   = pp_not_used     !: meridional grid-spacing (meters ) 
     94 
    7395 
    7496   !!  Coefficients associated with the vertical coordinate system 
    7597 
    7698#if key_orca_r1==75 
    77    REAL(wp), PARAMETER  ::       & 
    78       &     ppsur =  -3958.951371276829_wp ,  &  !: ORCA r1 coefficients 
     99   REAL(wp), PARAMETER  ::                     & 
     100      &     ppsur =   -3958.951371276829_wp ,  &  !: ORCA r1 coefficients 
    79101      &     ppa0  =   103.9530096000000_wp  ,  &  !: (75 levels case) 
    80102      &     ppa1  =   2.415951269000000_wp  ,  &  !: 
     
    82104      !                                           !: layer number above which  stretching will 
    83105      !                                           !: be maximum. Usually of order jpk/2. 
    84       &     ppacr =       7.00000000000_wp        !: (non dimensional): stretching factor 
     106      &     ppacr =   7.00000000000_wp            !: (non dimensional): stretching factor 
    85107      !                                           !: for the grid. The higher zacr, the smaller 
    86108      !                                           !: the stretching. 
    87    !! 
    88    !!  If both ppa0 ppa1 and ppsur are specified to pp_to_be_computed, then 
    89    !!  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
    90    !! 
     109 
     110      !  If both ppa0 ppa1 and ppsur are specified to pp_to_be_computed, then 
     111      !  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
     112 
    91113   REAL(wp), PARAMETER ::                      & 
    92114      &     ppdzmin = pp_not_used           ,  &  !: (meters) vertical thickness of the top layer 
    93115      &     pphmax  = pp_not_used                 !: (meters) Maximum depth of the ocean gdepw(jpk) 
    94    !! 
    95116   LOGICAL,  PARAMETER ::                      & 
    96117      &     ldbletanh = .TRUE.                    !: Use/do not use double tanf function for vertical coordinates 
    97118   REAL(wp), PARAMETER ::                      & 
    98       &     ppa2  =   100.7609285000000_wp  ,  &  !: Double tanh function parameters 
    99       &     ppkth2=   48.02989372000000_wp  ,  &  !: 
    100       &     ppacr2=    13.00000000000_wp          !: 
    101       ! 
     119      &     ppa2    = 100.7609285000000_wp  ,  &  !: Double tanh function parameters 
     120      &     ppkth2  = 48.02989372000000_wp  ,  &  !: 
     121      &     ppacr2  = 13.00000000000_wp           !: 
    102122#else 
    103    REAL(wp), PARAMETER  ::       & 
    104       &     ppsur = pp_to_be_computed ,        &  !: Computed in domzgr, set ppdzmin and pphmax below 
    105       &     ppa0  = pp_to_be_computed ,        &  !:    "           " 
    106       &     ppa1  = pp_to_be_computed ,        &  !:    "           " 
    107       ! 
    108       &     ppkth =  23.563_wp        ,        &  !: (non dimensional): gives the approximate 
     123   REAL(wp), PARAMETER  ::                     & 
     124      &     ppsur =   pp_to_be_computed     ,  &  !: Computed in domzgr, set ppdzmin and pphmax below 
     125      &     ppa0  =   pp_to_be_computed     ,  &  !:    "           " 
     126      &     ppa1  =   pp_to_be_computed     ,  &  !:    "           " 
     127      &     ppkth =   23.563_wp             ,  &  !: (non dimensional): gives the approximate 
    109128      !                                           !: layer number above which  stretching will 
    110129      !                                           !: be maximum. Usually of order jpk/2. 
    111130      &     ppacr =   9.00000000000_wp            !: (non dimensional): stretching factor 
    112       !                                           !: for the grid. The highest zacr, the smallest 
     131      !                                           !: for the grid. The higher zacr, the smaller 
    113132      !                                           !: the stretching. 
    114    !! 
    115    !!  If both ppa0 ppa1 and ppsur are specified to pp_to_be_computed, then 
    116    !!  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
    117    !! 
     133 
     134      !  If both ppa0 ppa1 and ppsur are specified to pp_to_be_computed, then 
     135      !  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
     136 
    118137   REAL(wp), PARAMETER ::                      & 
    119       &     ppdzmin = 6._wp           ,        &  !: (meters) vertical thickness of the top layer 
     138      &     ppdzmin = 6._wp                 ,  &  !: (meters) vertical thickness of the top layer 
    120139      &     pphmax  = 5750._wp                    !: (meters) Maximum depth of the ocean gdepw(jpk) 
    121    !! 
    122140   LOGICAL,  PARAMETER ::                      & 
    123141      &     ldbletanh = .FALSE.                   !: Use/do not use double tanf function for vertical coordinates 
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/par_ORCA_R2.h90

    r2715 r4229  
    99   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    1010   !!---------------------------------------------------------------------- 
    11    CHARACTER (len=16)      & 
     11   CHARACTER (len=16)         & 
    1212#if !defined key_agrif 
    13       , PARAMETER  & 
     13      , PARAMETER             & 
    1414#endif 
    15       ::     
    16       cp_cfg = "orca"           !: name of the configuration  
    17    INTEGER     & 
     15      ::                       
     16      cp_cfg  =  "orca"          !: Name of the configuration 
     17   INTEGER                    & 
    1818#if !defined key_agrif 
    19       , PARAMETER  & 
     19      , PARAMETER             & 
    2020#endif 
    21       :: & 
    22       jp_cfg = 2,            &  !: resolution of the configuration (degrees) 
     21      ::                      & 
     22      jp_cfg  =  2     ,      &  !: Resolution of the configuration (degrees) 
    2323 
    24       ! data size              !!! * size of all input files * 
    25       jpidta  = 182,         &  !: 1st lateral dimension ( >= jpiglo ) 
    26       jpjdta  = 149,         &  !: 2nd    "       "      ( >= jpjglo ) 
    27       jpkdta  = 31              !: number of levels      ( >= jpk    )  
     24      ! Data domain size         !!! *  Size of all input files * 
     25      jpidta  =  182   ,      &  !: 1st lateral dimension ( >= jpiglo ) 
     26      jpjdta  =  149   ,      &  !: 2nd lateral dimension ( >= jpjglo ) 
     27      jpkdta  =  31    ,      &  !: Number of levels      ( >= jpk    ) 
    2828 
    29 #if defined key_antarctic 
    30       ! zoom domain size       !!! *  antarctic zoom  *  
    31    INTEGER     & 
    32 #if !defined key_agrif 
    33       , PARAMETER  & 
     29#if defined key_c1d 
     30      ! Zoom domain size         !!! *  C1D zoom  * 
     31      jpiglo  =  3     ,      &  !: 1st dimension of global domain --> i 
     32      jpjglo  =  3     ,      &  !: 2nd dimension of global domain --> j 
     33      ! Domain characteristics 
     34      jperio  =  0               !: Lateral cond. type (between 0 and 6) 
     35 
     36   INTEGER                    & 
     37      ::                      & 
     38      ! Starting position of the zoom 
     39      jpizoom =  1     ,      &  !: Left bottom (i,j) indices of the zoom 
     40      jpjzoom =  1               !: in data domain indices 
     41#elif defined key_antarctic 
     42      ! Zoom domain size         !!! *  Antarctic zoom  *  
     43      jpiglo  =  jpidta,      &  !: 1st dimension of global domain --> i 
     44      jpjglo  =  50    ,      &  !: 2nd dimension of global domain --> j 
     45      ! Starting position of the zoom 
     46      jpizoom =  1     ,      &  !: Left bottom (i,j) indices of the zoom 
     47      jpjzoom =  1     ,      &  !: in data domain indices 
     48      ! Domain characteristics 
     49      jperio  =  1               !: Lateral cond. type (between 0 and 6) 
     50#elif defined key_arctic 
     51      ! Zoom domain size         !!! *  Arctic zoom  * 
     52      jpiglo  =  142   ,      &  !: 1st dimension of global domain --> i 
     53      jpjglo  =  jpjdta-97+1, &  !: 2nd dimension of global domain --> j 
     54      ! Starting position of the zoom 
     55      jpizoom =  21    ,      &  !: Left bottom (i,j) indices of the zoom 
     56      jpjzoom =  97    ,      &  !: in data domain indices 
     57      ! Domain characteristics 
     58      jperio  =  3               !: Lateral cond. type (between 0 and 6) 
     59#else 
     60      ! Global domain size       !!! *  Global domain  * 
     61      jpiglo  =  jpidta,      &  !: 1st dimension of global domain --> i 
     62      jpjglo  =  jpjdta,      &  !: 2nd dimension of global domain --> j 
     63      ! Starting position of the zoom 
     64      jpizoom =  1     ,      &  !: Left bottom (i,j) indices of the zoom 
     65      jpjzoom =  1     ,      &  !: in data domain indices 
     66      ! Domain characteristics 
     67      jperio  =  4               !: Lateral cond. type (between 0 and 6) 
    3468#endif 
    35       :: & 
    36       jpiglo  = jpidta,      &  !: 1st dimension of global domain --> i 
    37       jpjglo  = 50,          &  !: 2nd    "                  "    --> j 
    38       ! zoom starting position 
    39       jpizoom =   1   ,      &  !: left bottom (i,j) indices of the zoom 
    40       jpjzoom =   1   ,      &  !: in data domain indices 
    41       ! Domain characteristics 
    42       jperio  =   1             !: lateral cond. type (between 0 and 6) 
    4369 
    44 #elif defined key_arctic 
    45       ! zoom domain size       !!! *  arctic zoom  * 
    46    INTEGER    & 
    47 #if !defined key_agrif 
    48       , PARAMETER  & 
    49 #endif 
    50       :: & 
    51       jpiglo  = 142   ,      &  !: 1st dimension of global domain --> i 
    52       jpjglo  = jpjdta-97+1, &  !: 2nd    "                  "    --> j 
    53       ! zoom starting position  
    54       jpizoom =  21   ,      &  !: left bottom (i,j) indices of the zoom 
    55       jpjzoom =  97   ,      &  !: in data domain indices 
    56       ! Domain characteristics 
    57       jperio  =   3             !: lateral cond. type (between 0 and 6) 
    58  
    59 #elif defined key_c1d 
    60       ! global domain size     !!! *  global domain  * 
    61    INTEGER    & 
    62 #if !defined key_agrif 
    63       , PARAMETER  & 
    64 #endif 
    65       :: & 
    66       jpiglo  = 3     ,      &  !: 1st dimension of global domain --> i 
    67       jpjglo  = 3     ,      &  !: 2nd    "                  "    --> j 
    68       ! starting position of the zoom  
    69       ! jpizoom =   61   ,    &  !: left bottom (i,j) indices of the zoom 
    70       ! jpjzoom =   133  ,    &  !: in data domain indices (160W,75N) 
    71       ! jpizoom =   61   ,    &  !: left bottom (i,j) indices of the zoom 
    72       ! jpjzoom =   110  ,    &  !: in data domain indices (160W,50N) 
    73       ! jpizoom =   61   ,    &  !: left bottom (i,j) indices of the zoom 
    74       ! jpjzoom =   97   ,    &  !: in data domain indices (160W,30N) 
    75       ! jpizoom =   61   ,    &  !: left bottom (i,j) indices of the zoom 
    76       ! jpjzoom =   86   ,    &  !: in data domain indices (160W,10N) 
    77       ! jpizoom =   61   ,    &  !: left bottom (i,j) indices of the zoom 
    78       ! jpjzoom =   49   ,    &  !: in data domain indices (160W,30S) 
    79       ! jpizoom =   61   ,    &  !: left bottom (i,j) indices of the zoom 
    80       ! jpjzoom =   27   ,    &  !: in data domain indices (160W,60S) 
    81       ! jpizoom =   61   ,    &  !: left bottom (i,j) indices of the zoom 
    82       ! jpjzoom =    7   ,    &  !: in data domain indices (160W,75S) 
    83       jpizoom =   110   ,    &  !: left bottom (i,j) indices of the zoom 
    84       jpjzoom =   97   ,    &  !: in data domain indices (64W,31.5N) BATS site 
    85       ! Domain characteristics 
    86       jperio  =   0            !: lateral cond. type (between 0 and 6) 
    87 #else 
    88       ! global domain size     !!! *  global domain  * 
    89    INTEGER    & 
    90 #if !defined key_agrif 
    91       , PARAMETER  & 
    92 #endif 
    93       :: & 
    94       jpiglo  = jpidta,      &  !: 1st dimension of global domain --> i 
    95       jpjglo  = jpjdta,      &  !: 2nd    "                  "    --> j 
    96       ! starting position of the zoom  
    97       jpizoom =   1   ,      &  !: left bottom (i,j) indices of the zoom 
    98       jpjzoom =   1   ,      &  !: in data domain indices 
    99       ! Domain characteristics 
    100       jperio  =   4             !: lateral cond. type (between 0 and 6) 
    101  
    102 #endif 
    10370 
    10471   !!  Values set to pp_not_used indicates that this parameter is not used in THIS config. 
    10572   !!  Values set to pp_to_be_computed  indicates that variables will be computed in domzgr 
    106    REAL(wp), PARAMETER ::   & 
    107       pp_not_used       = 999999_wp , &  !: 
    108       pp_to_be_computed = 0._wp          !: 
    10973 
    110    !! Coefficients associated with the horizontal coordinate system (jphgr_msh /= 0 ) 
     74   REAL(wp), PARAMETER ::              & 
     75      pp_not_used       = 999999._wp , &  !: 
     76      pp_to_be_computed = 0._wp           !: 
    11177 
    112    INTEGER,PARAMETER   ::    & ! 
    113       jphgr_msh = 0            !: type of horizontal mesh 
    114       !                        !  = 0 curvilinear coordinate on the sphere 
    115       !                        !      read in coordinate.nc file 
    116       !                        !  = 1 geographical mesh on the sphere 
    117       !                        !      with regular grid-spacing 
    118       !                        !  = 2 f-plane with regular grid-spacing 
    119       !                        !  = 3 beta-plane with regular grid-spacing 
    120       !                        !  = 4 Mercator grid with T/U point at the equator  with 
    121       !                        !      isotropic resolution (e1_deg) 
     78 
     79   !! Coefficients associated with the horizontal coordinate system 
     80 
     81   INTEGER, PARAMETER  ::     & 
     82      jphgr_msh = 0              !: type of horizontal mesh 
     83      !                          !: = 0 curvilinear coordinate on the sphere 
     84      !                          !:     read in coordinate.nc file 
     85      !                          !: = 1 geographical mesh on the sphere 
     86      !                          !:     with regular grid-spacing 
     87      !                          !: = 2 f-plane with regular grid-spacing 
     88      !                          !: = 3 beta-plane with regular grid-spacing 
     89      !                          !: = 4 Mercator grid with T/U point at the equator  with 
     90      !                          !:     isotropic resolution (e1_deg) 
    12291 
    12392      !   ppglam0 , ppgphi0: coordinates of the lower leftmost T point of the grid. 
    12493      !   The mercator grid starts only approximately at gphi0 because 
    12594      !   of the constraint that the equator be a T point. 
    126    REAL(wp) ,PARAMETER ::       &  ! 
    127       ppglam0  = pp_not_used,   &  !: longitude of first raw and column T-point (jphgr_msh = 1) 
    128       ppgphi0  = pp_not_used,   &  !: latitude  of first raw and column T-point (jphgr_msh = 1) 
    129       !                            !  latitude for the Coriolis or Beta parameter (jphgr_msh = 2 or 3) 
    130       ppe1_deg = pp_not_used,   &  !: zonal      grid-spacing (degrees) 
    131       ppe2_deg = pp_not_used,   &  !: meridional grid-spacing (degrees) 
     95 
     96   REAL(wp), PARAMETER ::     & 
     97      ppglam0  = pp_not_used, &  !: longitude of first raw and column T-point   (jphgr_msh = 1) 
     98      ppgphi0  = pp_not_used, &  !: latitude  of first raw and column T-point   (jphgr_msh = 1) 
     99      !                          !: latitude for the Coriolis or Beta parameter (jphgr_msh = 2 or 3) 
     100      ppe1_deg = pp_not_used, &  !: zonal      grid-spacing (degrees) 
     101      ppe2_deg = pp_not_used, &  !: meridional grid-spacing (degrees) 
    132102      ! 
    133       ppe1_m   = pp_not_used,   &  !: zonal      grid-spacing (meters ) 
    134       ppe2_m   = pp_not_used       !: meridional grid-spacing (meters ) 
     103      ppe1_m   = pp_not_used, &  !: zonal      grid-spacing (meters ) 
     104      ppe2_m   = pp_not_used     !: meridional grid-spacing (meters ) 
    135105 
    136    !! 
    137    !! Vertical grid parameter for domzgr 
    138    !! ================================== 
    139    !! 
    140    REAL(wp), PARAMETER  ::       & 
    141       &     ppsur = -4762.96143546300_wp    ,  &  !: ORCA r4, r2 and r05 coefficients 
     106 
     107   !!  Coefficients associated with the vertical coordinate system 
     108 
     109   REAL(wp), PARAMETER  ::                     & 
     110      &     ppsur =   -4762.96143546300_wp  ,  &  !: ORCA r4, r2 and r05 coefficients 
    142111      &     ppa0  =   255.58049070440_wp    ,  &  !: (default coefficients) 
    143112      &     ppa1  =   245.58132232490_wp    ,  &  !: 
    144       &     ppkth =    21.43336197938_wp    ,  &  !: (non dimensional): gives the approximate 
     113      &     ppkth =   21.43336197938_wp     ,  &  !: (non dimensional): gives the approximate 
    145114      !                                           !: layer number above which  stretching will 
    146115      !                                           !: be maximum. Usually of order jpk/2. 
    147       &     ppacr =     3.00000000000_wp          !: (non dimensional): stretching factor 
    148       !                                           !: for the grid. The highest zacr, the smallest 
     116      &     ppacr =   3.00000000000_wp            !: (non dimensional): stretching factor 
     117      !                                           !: for the grid. The higher zacr, the smaller 
    149118      !                                           !: the stretching. 
    150119 
    151    !! 
    152    !!  If both ppa0 ppa1 and ppsur are specified to 0, then 
    153    !!  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
    154    !! 
    155    REAL(wp), PARAMETER ::        & 
     120      !  If both ppa0 ppa1 and ppsur are specified to pp_to_be_computed, then 
     121      !  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
     122 
     123   REAL(wp), PARAMETER ::                      & 
    156124      &     ppdzmin = pp_not_used           ,  &  !: (meters) vertical thickness of the top layer 
    157125      &     pphmax  = pp_not_used                 !: (meters) Maximum depth of the ocean gdepw(jpk) 
    158    LOGICAL,  PARAMETER ::        & 
     126   LOGICAL,  PARAMETER ::                      & 
    159127      &     ldbletanh = .FALSE.                   !: Use/do not use double tanf function for vertical coordinates 
    160    REAL(wp), PARAMETER ::        & 
     128   REAL(wp), PARAMETER ::                      & 
    161129      &     ppa2    = pp_not_used           ,  &  !: Double tanh function parameters 
    162130      &     ppkth2  = pp_not_used           ,  &  !: 
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/par_ORCA_R4.h90

    r2715 r4229  
    11   !!--------------------------------------------------------------------- 
    2    !!                     ***  par_ORCA_R4.h90  ***    
     2   !!                     ***  par_ORCA_R4.h90  ***   
    33   !!   Ocean Domain : 4 degrees resolution global ocean 
    44   !!                  (0RCA_R4 configuration) 
     
    99   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    1010   !!---------------------------------------------------------------------- 
    11    CHARACTER (len=16)      & 
     11   CHARACTER (len=16)         & 
    1212#if !defined key_agrif 
    13       , PARAMETER  & 
     13      , PARAMETER             & 
    1414#endif 
    15        ::    &   
    16      cp_cfg = "orca"           !: name of the configuration 
    17    INTEGER     & 
     15      ::                      &   
     16      cp_cfg  =  "orca"          !: Name of the configuration 
     17   INTEGER                    & 
    1818#if !defined key_agrif 
    19       , PARAMETER  & 
     19      , PARAMETER             & 
    2020#endif 
    21       :: & 
    22       jp_cfg = 4      ,      &  !: resolution of the configuration (degrees) 
    23       ! Original data size 
    24       jpidta  =  92   ,      &  !: first horizontal dimension > or = to jpi 
    25       jpjdta  =  76   ,      &  !: second                     > or = to jpj 
    26       jpkdta  =  31   ,      &  !: number of levels           > or = to jpk 
    27       ! global domain matrix size 
    28       jpiglo  = jpidta,      &  !: first  dimension of global domain --> i 
    29       jpjglo  = jpjdta,      &  !: second dimension of global domain --> j 
    30       ! starting position of the zoom 
    31       jpizoom =   1   ,      &  !: left bottom (i,j) indices of the zoom 
    32       jpjzoom =   1   ,      &  !: in data indices 
     21      ::                      & 
     22      jp_cfg  =  4     ,      &  !: Resolution of the configuration (degrees) 
     23 
     24      ! Data domain size         !!! *  Size of all input files  * 
     25      jpidta  =  92    ,      &  !: 1st lateral dimension ( >= jpiglo ) 
     26      jpjdta  =  76    ,      &  !: 2nd lateral dimension ( >= jpjglo ) 
     27      jpkdta  =  31    ,      &  !: Number of levels      ( >= jpk    ) 
     28 
     29#if defined key_c1d 
     30      ! Zoom domain size         !!! *  C1D zoom  * 
     31      jpiglo  =  3     ,      &  !: 1st dimension of global domain --> i 
     32      jpjglo  =  3     ,      &  !: 2nd dimension of global domain --> j 
    3333      ! Domain characteristics 
    34       jperio  =   4             !: lateral cond. type (between 0 and 6) 
     34      jperio  =  0               !: Lateral cond. type (between 0 and 6) 
     35 
     36   INTEGER                    & 
     37      ::                      & 
     38      ! Starting position of the zoom 
     39      jpizoom =  1     ,      &  !: Left bottom (i,j) indices of the zoom 
     40      jpjzoom =  1               !: in data domain indices 
     41#else 
     42      ! Global domain size       !!! *  Global domain  * 
     43      jpiglo  =  jpidta,      &  !: 1st dimension of global domain --> i 
     44      jpjglo  =  jpjdta,      &  !: 2nd dimension of global domain --> j 
     45      ! Starting position of the zoom 
     46      jpizoom =  1     ,      &  !: Left bottom (i,j) indices of the zoom 
     47      jpjzoom =  1     ,      &  !: in data domain indices 
     48      ! Domain characteristics 
     49      jperio  =  4               !: Lateral cond. type (between 0 and 6) 
     50#endif 
     51 
    3552 
    3653   !!  Values set to pp_not_used indicates that this parameter is not used in THIS config. 
    3754   !!  Values set to pp_to_be_computed  indicates that variables will be computed in domzgr 
    38    REAL(wp), PARAMETER ::   & 
    39       pp_not_used       = 999999_wp , &  !: 
    40       pp_to_be_computed = 0._wp          !: 
    4155 
    42    !! Coefficients associated with the horizontal coordinate system (jphgr_msh /= 0 ) 
    43    INTEGER, PARAMETER ::     & ! 
    44       jphgr_msh = 0            !: type of horizontal mesh 
    45       !                        ! = 0 curvilinear coordinate on the sphere 
    46       !                        !     read in coordinate.nc file 
    47       !                        ! = 1 geographical mesh on the sphere 
    48       !                        !     with regular grid-spacing 
    49       !                        ! = 2 f-plane with regular grid-spacing 
    50       !                        ! = 3 beta-plane with regular grid-spacing 
    51       !                        ! = 4 Mercator grid with T/U point at the equator  with 
    52       !                        !     isotropic resolution (e1_deg) 
     56   REAL(wp), PARAMETER ::              & 
     57      pp_not_used       = 999999._wp , &  !: 
     58      pp_to_be_computed = 0._wp           !: 
     59 
     60 
     61   !! Coefficients associated with the horizontal coordinate system 
     62 
     63   INTEGER, PARAMETER  ::     & 
     64      jphgr_msh = 0              !: type of horizontal mesh 
     65      !                          !: = 0 curvilinear coordinate on the sphere 
     66      !                          !:     read in coordinate.nc file 
     67      !                          !: = 1 geographical mesh on the sphere 
     68      !                          !:     with regular grid-spacing 
     69      !                          !: = 2 f-plane with regular grid-spacing 
     70      !                          !: = 3 beta-plane with regular grid-spacing 
     71      !                          !: = 4 Mercator grid with T/U point at the equator  with 
     72      !                          !:     isotropic resolution (e1_deg) 
    5373 
    5474      !   ppglam0 , ppgphi0: coordinates of the lower leftmost T point of the grid. 
    5575      !   The mercator grid starts only approximately at gphi0 because 
    5676      !   of the constraint that the equator be a T point. 
    57    REAL(wp) , PARAMETER ::      &  ! 
    58       ppglam0  = pp_not_used,   &  !: longitude of first raw and column T-point (jphgr_msh = 1) 
    59       ppgphi0  = pp_not_used,   &  !: latitude  of first raw and column T-point (jphgr_msh = 1) 
    60       !                            ! latitude for the Coriolis or Beta parameter (jphgr_msh = 2 or 3) 
    61       ppe1_deg = pp_not_used,   &  !: zonal      grid-spacing (degrees) 
    62       ppe2_deg = pp_not_used,   &  !: meridional grid-spacing (degrees) 
     77 
     78   REAL(wp), PARAMETER ::     & 
     79      ppglam0  = pp_not_used, &  !: longitude of first raw and column T-point   (jphgr_msh = 1) 
     80      ppgphi0  = pp_not_used, &  !: latitude  of first raw and column T-point   (jphgr_msh = 1) 
     81      !                          !: latitude for the Coriolis or Beta parameter (jphgr_msh = 2 or 3) 
     82      ppe1_deg = pp_not_used, &  !: zonal      grid-spacing (degrees) 
     83      ppe2_deg = pp_not_used, &  !: meridional grid-spacing (degrees) 
    6384      ! 
    64       ppe1_m   = pp_not_used,   &  !: zonal      grid-spacing (meters ) 
    65       ppe2_m   = pp_not_used       !: meridional grid-spacing (meters ) 
     85      ppe1_m   = pp_not_used, &  !: zonal      grid-spacing (meters ) 
     86      ppe2_m   = pp_not_used     !: meridional grid-spacing (meters ) 
    6687 
    6788 
    68    !! Vertical grid parameter for domzgr 
    69    !! ================================== 
     89   !!  Coefficients associated with the vertical coordinate system 
    7090 
    71    REAL(wp), PARAMETER  ::       & 
    72       &     ppsur = -4762.96143546300_wp    ,  &  !: ORCA r4, r2 and r05 coefficients 
     91   REAL(wp), PARAMETER  ::                     & 
     92      &     ppsur =   -4762.96143546300_wp  ,  &  !: ORCA r4, r2 and r05 coefficients 
    7393      &     ppa0  =   255.58049070440_wp    ,  &  !: (default coefficients) 
    7494      &     ppa1  =   245.58132232490_wp    ,  &  !: 
    75       &     ppkth =    21.43336197938_wp    ,  &  !: (non dimensional): gives the approximate 
     95      &     ppkth =   21.43336197938_wp     ,  &  !: (non dimensional): gives the approximate 
    7696      !                                           !: layer number above which  stretching will 
    7797      !                                           !: be maximum. Usually of order jpk/2. 
    78       &     ppacr =     3.00000000000_wp          !: (non dimensional): stretching factor 
    79       !                                           !: for the grid. The highest zacr, the smallest 
     98      &     ppacr =   3.00000000000_wp            !: (non dimensional): stretching factor 
     99      !                                           !: for the grid. The higher zacr, the smaller 
    80100      !                                           !: the stretching. 
    81101 
    82    !!  If both ppa0 ppa1 and ppsur are specified to 0, then 
    83    !!  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
     102      !  If both ppa0 ppa1 and ppsur are specified to pp_to_be_computed, then 
     103      !  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
    84104 
    85    REAL(wp), PARAMETER ::        & 
     105   REAL(wp), PARAMETER ::                      & 
    86106      &     ppdzmin = pp_not_used           ,  &  !: (meters) vertical thickness of the top layer 
    87107      &     pphmax  = pp_not_used                 !: (meters) Maximum depth of the ocean gdepw(jpk) 
    88    LOGICAL,  PARAMETER ::        & 
     108   LOGICAL,  PARAMETER ::                      & 
    89109      &     ldbletanh = .FALSE.                   !: Use/do not use double tanf function for vertical coordinates 
    90    REAL(wp), PARAMETER ::        & 
     110   REAL(wp), PARAMETER ::                      & 
    91111      &     ppa2    = pp_not_used           ,  &  !: Double tanh function parameters 
    92112      &     ppkth2  = pp_not_used           ,  &  !: 
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/par_POMME_R025.h90

    r3294 r4229  
    99   !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    1010   !!---------------------------------------------------------------------- 
    11    CHARACTER (len=16)      & 
     11   CHARACTER (len=16)         & 
    1212#if !defined key_agrif 
    13       , PARAMETER  & 
     13      , PARAMETER             & 
    1414#endif 
    15       ::     
    16       cp_cfg = "pomme"          !: POMME025 name of the configuration 
    17    INTEGER     & 
     15      ::                       
     16      cp_cfg  =  "pomme"         !: Name of the configuration 
     17   INTEGER                    & 
    1818#if !defined key_agrif 
    19       , PARAMETER  & 
     19      , PARAMETER             & 
    2020#endif 
    21       :: & 
    22       jp_cfg = 025  ,        &  !: resolution of the configuration (degrees) 
    23       ! Original data size 
     21      ::                      & 
     22      jp_cfg  =  025   ,      &  !: Resolution of the configuration (degrees) 
     23 
    2424      ! ORCA025 global grid size 
    25       jpiglo_ORCA025 = 1442, & 
    26       jpjglo_ORCA025 = 1021, &  ! not used currently 
     25      jpiglo_ORCA025 = 1442,  & 
     26      jpjglo_ORCA025 = 1021,  &  ! not used currently 
    2727      ! POMME "global" domain localisation in the ORCA025 global grid 
    28       jpi_iw    = 1059,      &  
    29       jpi_ie    = 1088,      &   
    30       jpj_js    = 661,       & 
    31       jpj_jn    = 700,       & 
    32       jpidta  = ( jpi_ie - jpi_iw + 1 ), &   !: =30 first horizontal dimension > or = to jpi 
    33       jpjdta  = ( jpj_jn - jpj_js + 1 ), &   !: =40 second                     > or = to jpj 
    34       jpkdta  = 46 ,         &  !: number of levels           > or = to jpk 
    35       ! total domain matrix size 
    36       jpiglo  = jpidta,      &  !: first  dimension of global domain --> i 
    37       jpjglo  = jpjdta,      &  !: second dimension of global domain --> j 
    38       ! starting position of the zoom 
    39       jpizoom =   1   ,      &  !: left bottom (i,j) indices of the zoom 
    40       jpjzoom =   1   ,      &  !: in data indices 
     28      jpi_iw  =  1059  ,      &  
     29      jpi_ie  =  1088  ,      &   
     30      jpj_js  =  661   ,      & 
     31      jpj_jn  =  700   ,      & 
     32 
     33      ! Data domain size                      !!! *  Size of all input files  * 
     34      jpidta  =  ( jpi_ie - jpi_iw + 1 ), &   !: =30 1st lateral dimension ( >= jpiglo ) 
     35      jpjdta  =  ( jpj_jn - jpj_js + 1 ), &   !: =40 2nd lateral dimension ( >= jpjglo ) 
     36      jpkdta  =  46    ,      &               !: Number of levels          ( >= jpk    ) 
     37 
     38      ! Global domain size       !!! *  Global domain  * 
     39      jpiglo  =  jpidta,      &  !: 1st dimension of global domain --> i 
     40      jpjglo  =  jpjdta,      &  !: 2nd dimension of global domain --> j 
     41      ! Starting position of the zoom 
     42      jpizoom =  1     ,      &  !: Left bottom (i,j) indices of the zoom 
     43      jpjzoom =  1     ,      &  !: in data domain indices 
    4144      ! Domain characteristics 
    42       jperio  =    0            !: lateral cond. type (between 0 and 6) 
     45      jperio  =  0               !: Lateral cond. type (between 0 and 6) 
     46 
    4347 
    4448   !!  Values set to pp_not_used indicates that this parameter is not used in THIS config. 
    4549   !!  Values set to pp_to_be_computed  indicates that variables will be computed in domzgr 
    46    REAL,PARAMETER      ::  pp_not_used = 999999_wp , & 
    47       &                    pp_to_be_computed = 0._wp 
    48    !! 
    49    !! Coefficients associated with the horizontal coordinate system (jphgr_msh /= 0 ) 
    50    !! 
    51    INTEGER, PARAMETER ::     & ! 
    52       jphgr_msh = 0            !: type of horizontal mesh 
    53       !                        !  = 0 curvilinear coordinate on the sphere 
    54       !                        !      read in coordinate.nc file 
    55       !                        !  = 1 geographical mesh on the sphere 
    56       !                        !      with regular grid-spacing 
    57       !                        !  = 2 f-plane with regular grid-spacing 
    58       !                        !  = 3 beta-plane with regular grid-spacing 
    59       !                        !  = 4 Mercator grid with T/U point at the equator  with 
    60       !                        !      isotropic resolution (e1_deg) 
     50 
     51   REAL(wp), PARAMETER ::              & 
     52      pp_not_used       = 999999._wp , &  !: 
     53      pp_to_be_computed = 0._wp           !: 
     54 
     55 
     56   !! Coefficients associated with the horizontal coordinate system 
     57 
     58   INTEGER, PARAMETER  ::     & 
     59      jphgr_msh = 0              !: type of horizontal mesh 
     60      !                          !: = 0 curvilinear coordinate on the sphere 
     61      !                          !:     read in coordinate.nc file 
     62      !                          !: = 1 geographical mesh on the sphere 
     63      !                          !:     with regular grid-spacing 
     64      !                          !: = 2 f-plane with regular grid-spacing 
     65      !                          !: = 3 beta-plane with regular grid-spacing 
     66      !                          !: = 4 Mercator grid with T/U point at the equator  with 
     67      !                          !:     isotropic resolution (e1_deg) 
    6168 
    6269      !   ppglam0 , ppgphi0: coordinates of the lower leftmost T point of the grid. 
    6370      !   The mercator grid starts only approximately at gphi0 because 
    6471      !   of the constraint that the equator be a T point. 
    65    REAL(wp), PARAMETER ::       &  ! 
    66       ppglam0  = pp_not_used,   &  !: longitude of first raw and column T-point (jphgr_msh = 1) 
    67       ppgphi0  = pp_not_used,   &  !: latitude  of first raw and column T-point (jphgr_msh = 1) 
    68       !                            !  latitude for the Coriolis or Beta parameter (jphgr_msh = 2 or 3) 
    69       ppe1_deg = pp_not_used,   &  !: zonal      grid-spacing (degrees) 
    70       ppe2_deg = pp_not_used,   &  !: meridional grid-spacing (degrees) 
     72 
     73   REAL(wp), PARAMETER ::     & 
     74      ppglam0  = pp_not_used, &  !: longitude of first raw and column T-point   (jphgr_msh = 1) 
     75      ppgphi0  = pp_not_used, &  !: latitude  of first raw and column T-point   (jphgr_msh = 1) 
     76      !                          !: latitude for the Coriolis or Beta parameter (jphgr_msh = 2 or 3) 
     77      ppe1_deg = pp_not_used, &  !: zonal      grid-spacing (degrees) 
     78      ppe2_deg = pp_not_used, &  !: meridional grid-spacing (degrees) 
    7179      ! 
    72       ppe1_m   = pp_not_used,   &  !: zonal      grid-spacing (meters ) 
    73       ppe2_m   = pp_not_used       !: meridional grid-spacing (meters ) 
     80      ppe1_m   = pp_not_used, &  !: zonal      grid-spacing (meters ) 
     81      ppe2_m   = pp_not_used     !: meridional grid-spacing (meters ) 
     82 
    7483 
    7584   !!  Coefficients associated with the vertical coordinate system 
    7685 
    77    REAL(wp), PARAMETER  ::       & 
    78       &     ppsur = pp_to_be_computed ,  &  !: Computed in domzgr, set ppdzmin and pphmax below 
    79       &     ppa0  = pp_to_be_computed ,  &  !:    "           " 
    80       &     ppa1  = pp_to_be_computed ,  &  !:    "           " 
    81       ! 
    82       &     ppkth =  23.563_wp        ,  &  !: (non dimensional): gives the approximate 
    83       !                                     !: layer number above which  stretching will 
    84       !                                     !: be maximum. Usually of order jpk/2. 
    85       &     ppacr =    9.00000000000_wp     !: (non dimensional): stretching factor 
    86       !                                     !: for the grid. The highest zacr, the smallest 
    87       !                                     !: the stretching. 
     86   REAL(wp), PARAMETER ::                      & 
     87      &     ppsur =   pp_to_be_computed     ,  &  !: Computed in domzgr, set ppdzmin and pphmax below 
     88      &     ppa0  =   pp_to_be_computed     ,  &  !:    "           " 
     89      &     ppa1  =   pp_to_be_computed     ,  &  !:    "           " 
     90      &     ppkth =   23.563_wp             ,  &  !: (non dimensional): gives the approximate 
     91      !                                           !: layer number above which  stretching will 
     92      !                                           !: be maximum. Usually of order jpk/2. 
     93      &     ppacr =   9.00000000000_wp            !: (non dimensional): stretching factor 
     94      !                                           !: for the grid. The higher zacr, the smaller 
     95      !                                           !: the stretching. 
    8896 
    89    !! 
    90    !!  If both ppa0 ppa1 and ppsur are specified to 0, then 
    91    !!  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
    92    !! 
    93    REAL(wp), PARAMETER ::        & 
    94       &     ppdzmin = 6._wp           ,  &  !: (meters) vertical thickness of the top layer 
    95       &     pphmax  = 5750._wp              !: (meters) Maximum depth of the ocean gdepw(jpk) 
    96    LOGICAL,  PARAMETER ::        & 
    97       &     ldbletanh = .FALSE.             !: Use/do not use double tanf function for vertical coordinates 
    98    REAL(wp), PARAMETER ::        & 
    99       &     ppa2    = pp_not_used     ,  &  !: Double tanh function parameters 
    100       &     ppkth2  = pp_not_used     ,  &  !: 
    101       &     ppacr2  = pp_not_used           !: 
     97      !  If both ppa0 ppa1 and ppsur are specified to pp_to_be_computed, then 
     98      !  they are computed from ppdzmin, pphmax , ppkth, ppacr in dom_zgr 
     99 
     100   REAL(wp), PARAMETER ::                      & 
     101      &     ppdzmin = 6._wp                 ,  &  !: (meters) vertical thickness of the top layer 
     102      &     pphmax  = 5750._wp                    !: (meters) Maximum depth of the ocean gdepw(jpk) 
     103   LOGICAL,  PARAMETER ::                      & 
     104      &     ldbletanh = .FALSE.                   !: Use/do not use double tanf function for vertical coordinates 
     105   REAL(wp), PARAMETER ::                      & 
     106      &     ppa2    = pp_not_used           ,  &  !: Double tanh function parameters 
     107      &     ppkth2  = pp_not_used           ,  &  !: 
     108      &     ppacr2  = pp_not_used                 !: 
    102109   !!--------------------------------------------------------------------- 
  • branches/2013/dev_MERCATOR_UKMO_2013/NEMOGCM/NEMO/OPA_SRC/par_oce.F90

    r4228 r4229  
    104104 
    105105   ! global or zoom domain size                      !!! * computational domain * 
     106#if defined key_c1d 
     107   INTEGER, PUBLIC, PARAMETER ::   jpiglo  = 3        !: 1st dimension of global domain --> i 
     108   INTEGER, PUBLIC, PARAMETER ::   jpjglo  = 3        !: 2nd    -                  -    --> j 
     109 
     110   ! zoom starting position  
     111   INTEGER, PUBLIC            ::   jpizoom =   1      !: left bottom (i,j) indices of the zoom 
     112   INTEGER, PUBLIC            ::   jpjzoom =   1      !: in data domain indices 
     113#else 
    106114   INTEGER, PUBLIC, PARAMETER ::   jpiglo  = jpidta   !: 1st dimension of global domain --> i 
    107115   INTEGER, PUBLIC, PARAMETER ::   jpjglo  = jpjdta   !: 2nd    -                  -    --> j 
     
    110118   INTEGER, PUBLIC, PARAMETER ::   jpizoom =   1      !: left bottom (i,j) indices of the zoom 
    111119   INTEGER, PUBLIC, PARAMETER ::   jpjzoom =   1      !: in data domain indices 
     120#endif 
    112121 
    113122   ! Domain characteristics 
Note: See TracChangeset for help on using the changeset viewer.