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 4162 – NEMO

Changeset 4162


Ignore:
Timestamp:
2013-11-07T11:19:49+01:00 (10 years ago)
Author:
cetlod
Message:

dev_LOCEAN_2013 : merge in trunk changes between r4028 and r4119, see ticket #1169

Location:
branches/2013/dev_LOCEAN_2013/NEMOGCM
Files:
1 deleted
15 edited
1 copied

Legend:

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

    r4147 r4162  
    675675      ! used to prevent the applied increments taking the temperature below the local freezing point  
    676676 
    677 #if defined key_cice  
    678         fzptnz(:,:,:) = -1.8_wp 
    679 #else  
    680         DO jk = 1, jpk 
    681            DO jj = 1, jpj 
    682               DO ji = 1, jpk 
    683                  fzptnz (ji,jj,jk) = ( -0.0575_wp + 1.710523e-3_wp * SQRT( tsn(ji,jj,jk,jp_sal) )                   &  
    684                                                   - 2.154996e-4_wp *       tsn(ji,jj,jk,jp_sal)   ) * tsn(ji,jj,jk,jp_sal)  &  
    685                                                   - 7.53e-4_wp * fsdepw(ji,jj,jk)       ! (pressure in dbar)  
    686               END DO 
    687            END DO 
    688         END DO 
    689 #endif  
     677      DO jk=1, jpkm1 
     678         fzptnz (:,:,jk) = tfreez( tsn(:,:,jk,jp_sal), fsdept(:,:,jk) ) 
     679      ENDDO 
    690680 
    691681      IF ( ln_asmiau ) THEN 
  • branches/2013/dev_LOCEAN_2013/NEMOGCM/NEMO/OPA_SRC/DIA/diahsb.F90

    r4161 r4162  
    3636   LOGICAL, PUBLIC ::   ln_diahsb   !: check the heat and salt budgets 
    3737 
    38    REAL(wp), SAVE                                ::   frc_t      , frc_s     , frc_v   ! global forcing trends 
    39    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   ssh_ini              ! 
    40    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   hc_loc_ini, sc_loc_ini, e3t_ini  ! 
    41    REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   hcssh_loc_ini, scssh_loc_ini     ! 
     38   REAL(dp), SAVE                                ::   frc_t      , frc_s     , frc_v   ! global forcing trends 
     39   REAL(dp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   ssh_ini              ! 
     40   REAL(dp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   hc_loc_ini, sc_loc_ini, e3t_ini  ! 
     41   REAL(dp), ALLOCATABLE, SAVE, DIMENSION(:,:)   ::   hcssh_loc_ini, scssh_loc_ini     ! 
    4242 
    4343   !! * Substitutions 
     
    6767      !! 
    6868      INTEGER    ::   jk                          ! dummy loop indice 
    69       REAL(wp)   ::   zdiff_hc    , zdiff_sc      ! heat and salt content variations 
    70       REAL(wp)   ::   zdiff_v1    , zdiff_v2      ! volume variation 
    71       REAL(wp)   ::   z_hc        , z_sc          ! heat and salt content 
    72       REAL(wp)   ::   z_v1        , z_v2          ! volume 
    73       REAL(wp)   ::   zdeltat                     !    -     - 
    74       REAL(wp)   ::   z_frc_trd_t , z_frc_trd_s   !    -     - 
    75       REAL(wp)   ::   z_frc_trd_v                 !    -     - 
    76       REAL(wp), POINTER, DIMENSION(:,:)   ::   zsurf              ! 
     69      REAL(dp)   ::   zdiff_hc    , zdiff_sc      ! heat and salt content variations 
     70      REAL(dp)   ::   zdiff_v1    , zdiff_v2      ! volume variation 
     71      REAL(dp)   ::   z_hc        , z_sc          ! heat and salt content 
     72      REAL(dp)   ::   z_v1        , z_v2          ! volume 
     73      REAL(dp)   ::   zdeltat                     !    -     - 
     74      REAL(dp)   ::   z_frc_trd_t , z_frc_trd_s   !    -     - 
     75      REAL(dp)   ::   z_frc_trd_v                 !    -     - 
     76      REAL(dp), POINTER, DIMENSION(:,:)   ::   zsurf              ! 
    7777      !!--------------------------------------------------------------------------- 
    7878      IF( nn_timing == 1 )   CALL timing_start('dia_hsb')       
     
    8888      z_frc_trd_t =           glob_sum( sbc_tsc(:,:,jp_tem) * zsurf(:,:) )       ! heat fluxes 
    8989      z_frc_trd_s =           glob_sum( sbc_tsc(:,:,jp_sal) * zsurf(:,:) )       ! salt fluxes 
     90      ! 
     91      IF( ln_rnf    )   z_frc_trd_t = z_frc_trd_t + glob_sum( rnf_tsc(:,:,jp_tem) * zsurf(:,:) ) 
     92      IF( ln_rnf_sal)   z_frc_trd_s = z_frc_trd_s + glob_sum( rnf_tsc(:,:,jp_sal) * zsurf(:,:) ) 
     93 
    9094      ! Add penetrative solar radiation 
    9195      IF( ln_traqsr )   z_frc_trd_t = z_frc_trd_t + r1_rau0_rcp * glob_sum( qsr     (:,:) * zsurf(:,:) ) 
     
    100104      ! 2a -  Content variations ! 
    101105      ! ------------------------ ! 
    102       zdiff_v2 = 0._wp 
    103       zdiff_hc = 0._wp 
    104       zdiff_sc = 0._wp 
     106      zdiff_v2 = 0._dp 
     107      zdiff_hc = 0._dp 
     108      zdiff_sc = 0._dp 
    105109      ! volume variation (calculated with ssh) 
    106110      zdiff_v1 = glob_sum( zsurf(:,:) * ( sshn(:,:) - ssh_ini(:,:) ) ) 
     
    122126       
    123127      ! add ssh if not vvl 
    124 #if ! defined key_vvl 
    125      zdiff_v2 = zdiff_v2 + zdiff_v1 
    126      zdiff_hc = zdiff_hc + glob_sum( zsurf(:,:) * ( sshn(:,:) * tsn(:,:,1,jp_tem)   & 
    127             &                           - hcssh_loc_ini(:,:) ) ) 
    128      zdiff_sc = zdiff_sc + glob_sum( zsurf(:,:) * ( sshn(:,:) * tsn(:,:,1,jp_sal)   & 
    129             &                           - scssh_loc_ini(:,:) ) ) 
    130 #endif  
     128      IF( .NOT. lk_vvl ) THEN 
     129        zdiff_v2 = zdiff_v2 + zdiff_v1 
     130        zdiff_hc = zdiff_hc + glob_sum( zsurf(:,:) * ( sshn(:,:) * tsn(:,:,1,jp_tem)   & 
     131               &                           - hcssh_loc_ini(:,:) ) ) 
     132        zdiff_sc = zdiff_sc + glob_sum( zsurf(:,:) * ( sshn(:,:) * tsn(:,:,1,jp_sal)   & 
     133               &                           - scssh_loc_ini(:,:) ) ) 
     134      ENDIF 
    131135      ! 
    132136      ! ----------------------- ! 
    133137      ! 2b -  Content           ! 
    134138      ! ----------------------- ! 
    135       z_v2 = 0._wp 
    136       z_hc = 0._wp 
    137       z_sc = 0._wp 
     139      z_v2 = 0._dp 
     140      z_hc = 0._dp 
     141      z_sc = 0._dp 
    138142      ! volume (calculated with ssh) 
    139143      z_v1 = glob_sum( zsurf(:,:) * sshn(:,:) ) 
     
    147151      ENDDO 
    148152      ! add ssh if not vvl 
    149 #if ! defined key_vvl 
    150      z_v2 = z_v2 + z_v1 
    151      z_hc = z_hc + glob_sum( zsurf(:,:) * sshn(:,:) * tsn(:,:,1,jp_tem) ) 
    152      z_sc = z_sc + glob_sum( zsurf(:,:) * sshn(:,:) * tsn(:,:,1,jp_sal) ) 
    153 #endif  
     153      IF( .NOT. lk_vvl ) THEN 
     154        z_v2 = z_v2 + z_v1 
     155        z_hc = z_hc + glob_sum( zsurf(:,:) * sshn(:,:) * tsn(:,:,1,jp_tem) ) 
     156        z_sc = z_sc + glob_sum( zsurf(:,:) * sshn(:,:) * tsn(:,:,1,jp_sal) ) 
     157      ENDIF 
    154158 
    155159      ! ----------------------- ! 
     
    160164      CALL iom_put( 'bgtemper' , z_hc / z_v2 )                      ! Temperature (C)  
    161165      CALL iom_put( 'bgsaline' , z_sc / z_v2 )                      ! Salinity (psu) 
    162       CALL iom_put( 'bgheatco' , zdiff_hc * rau0 * rcp * 1.e-9_wp ) ! Heat content variation (10^9 J) 
     166      CALL iom_put( 'bgheatco' , zdiff_hc * rau0 * rcp * 1.e-9_dp ) ! Heat content variation (10^9 J) 
    163167      CALL iom_put( 'bgsaltco' , zdiff_sc * 1.e-9 )                 ! Salt content variation (psu*km3)  
    164168      CALL iom_put( 'bgvolssh' , zdiff_v1 * 1.e-9 )                    ! volume ssh (km3)   
     
    166170      CALL iom_put( 'bgvoltot' , zdiff_v2 * 1.e-9 )                 ! volume total (km3)  
    167171      CALL iom_put( 'bgfrcvol' , frc_v * 1.e-9 )                     ! vol - surface forcing (volume)  
    168       CALL iom_put( 'bgfrctem' , frc_t * rau0 * rcp * 1.e-9_wp ) ! hc  - surface forcing (heat content)  
     172      CALL iom_put( 'bgfrctem' , frc_t * rau0 * rcp * 1.e-9_dp ) ! hc  - surface forcing (heat content)  
    169173      CALL iom_put( 'bgfrcsal' , frc_s * 1.e-9 )                     ! sc  - surface forcing (salt content)  
    170174      ! 
     
    286290          hcssh_loc_ini(:,:) = tsn(:,:,1,jp_tem) * sshn(:,:)   ! initial heat content in ssh 
    287291          scssh_loc_ini(:,:) = tsn(:,:,1,jp_sal) * sshn(:,:)   ! initial salt content in ssh 
    288           frc_v = 0._wp                                            
    289           frc_t = 0._wp                                            
    290           frc_s = 0._wp                                                   
     292          frc_v = 0._dp                                            
     293          frc_t = 0._dp                                            
     294          frc_s = 0._dp                                                   
    291295       ENDIF 
    292296 
  • branches/2013/dev_LOCEAN_2013/NEMOGCM/NEMO/OPA_SRC/DOM/closea.F90

    r3632 r4162  
    108108            ncsi1(2)   =  97  ;  ncsj1(2)   = 107 
    109109            ncsi2(2)   = 103  ;  ncsj2(2)   = 111 
    110             ncsir(2,1) = 110  ;  ncsjr(2,1) = 111 
    111             !                                            ! Black Sea 1 : west part of the Black Sea  
    112             ncsnr(3)   = 1    ; ncstt(3)   =   2            !            (ie west of the cyclic b.c.) 
    113             ncsi1(3)   = 174  ; ncsj1(3)   = 107            ! put in Med Sea 
    114             ncsi2(3)   = 181  ; ncsj2(3)   = 112 
    115             ncsir(3,1) = 171  ; ncsjr(3,1) = 106  
    116             !                                            ! Black Sea 2 : est part of the Black Sea  
    117             ncsnr(4)   =   1  ;  ncstt(4)   =   2           !               (ie est of the cyclic b.c.) 
    118             ncsi1(4)   =   2  ;  ncsj1(4)   = 107           ! put in Med Sea 
    119             ncsi2(4)   =   6  ;  ncsj2(4)   = 112 
    120             ncsir(4,1) = 171  ;  ncsjr(4,1) = 106  
     110            ncsir(2,1) = 110  ;  ncsjr(2,1) = 111            
     111            !                                            ! Black Sea (crossed by the cyclic boundary condition) 
     112            ncsnr(3:4) =   4  ;  ncstt(3:4) =   2           ! put in Med Sea (north of Aegean Sea) 
     113            ncsir(3:4,1) = 171;  ncsjr(3:4,1) = 106         ! 
     114            ncsir(3:4,2) = 170;  ncsjr(3:4,2) = 106  
     115            ncsir(3:4,3) = 171;  ncsjr(3:4,3) = 105  
     116            ncsir(3:4,4) = 170;  ncsjr(3:4,4) = 105  
     117            ncsi1(3)   = 174  ;  ncsj1(3)   = 107           ! 1 : west part of the Black Sea       
     118            ncsi2(3)   = 181  ;  ncsj2(3)   = 112           !            (ie west of the cyclic b.c.) 
     119            ncsi1(4)   =   2  ;  ncsj1(4)   = 107           ! 2 : east part of the Black Sea  
     120            ncsi2(4)   =   6  ;  ncsj2(4)   = 112           !           (ie east of the cyclic b.c.) 
     121              
     122           
     123 
    121124            !                                        ! ======================= 
    122125         CASE ( 4 )                                  !  ORCA_R4 configuration 
     
    372375      REAL(wp), DIMENSION(jpi,jpj), INTENT(inout) ::   p_rnfmsk   ! river runoff mask (rnfmsk array) 
    373376      ! 
    374       INTEGER  ::   jc, jn      ! dummy loop indices 
    375       INTEGER  ::   ii, ij      ! temporary integer 
     377      INTEGER  ::   jc, jn, ji, jj      ! dummy loop indices 
    376378      !!---------------------------------------------------------------------- 
    377379      ! 
     
    379381         IF( ncstt(jc) >= 1 ) THEN            ! runoff mask set to 1 at closed sea outflows 
    380382             DO jn = 1, 4 
    381                ii = mi0( ncsir(jc,jn) ) 
    382                ij = mj0( ncsjr(jc,jn) ) 
    383                p_rnfmsk(ii,ij) = MAX( p_rnfmsk(ii,ij), 1.0_wp ) 
     383                DO jj =    mj0( ncsjr(jc,jn) ), mj1( ncsjr(jc,jn) ) 
     384                   DO ji = mi0( ncsir(jc,jn) ), mi1( ncsir(jc,jn) ) 
     385                      p_rnfmsk(ji,jj) = MAX( p_rnfmsk(ji,jj), 1.0_wp ) 
     386                   END DO 
     387                END DO 
    384388            END DO  
    385389         ENDIF  
  • branches/2013/dev_LOCEAN_2013/NEMOGCM/NEMO/OPA_SRC/DOM/daymod.F90

    r3851 r4162  
    238238               nday_year = 1 
    239239               nsec_year = ndt05 
     240               IF( nsec1jan000 >= 2 * (2**30 - nsecd * nyear_len(1) / 2 ) ) THEN   ! test integer 4 max value 
     241                  CALL ctl_stop( 'The number of seconds between Jan. 1st 00h of nit000 year and Jan. 1st 00h ',   & 
     242                     &           'of the current year is exceeding the INTEGER 4 max VALUE: 2^31-1 -> 68.09 years in seconds', & 
     243                     & 'You must do a restart at higher frequency (or remove this STOP and recompile everything in I8)' ) 
     244               ENDIF 
    240245               nsec1jan000 = nsec1jan000 + nsecd * nyear_len(1) 
    241246               IF( nleapy == 1 )   CALL day_mth 
  • branches/2013/dev_LOCEAN_2013/NEMOGCM/NEMO/OPA_SRC/LBC/lib_mpp.F90

    r4153 r4162  
    21862186        IF(((nbondi .ne. 0) .AND. (ktype .eq. 2)) .OR. ((nbondj .ne. 0) .AND. (ktype .eq. 1))) THEN 
    21872187            ! there is nothing to be migrated 
    2188                lmigr = .FALSE. 
     2188              lmigr = .TRUE. 
    21892189            ELSE 
    2190               lmigr = .TRUE. 
     2190              lmigr = .FALSE. 
    21912191            ENDIF 
    21922192 
  • branches/2013/dev_LOCEAN_2013/NEMOGCM/NEMO/OPA_SRC/SBC/geo2ocean.F90

    r2715 r4162  
    187187         &      gsinf(jpi,jpj), gcosf(jpi,jpj), STAT=ierr ) 
    188188      IF(lk_mpp)   CALL mpp_sum( ierr ) 
    189       IF( ierr /= 0 )   CALL ctl_stop('STOP', 'angle_msh_geo: unable to allocate arrays' ) 
     189      IF( ierr /= 0 )   CALL ctl_stop('angle: unable to allocate arrays' ) 
    190190 
    191191      ! ============================= ! 
     
    361361            &      gsinlat(jpi,jpj,4) , gcoslat(jpi,jpj,4) , STAT=ierr ) 
    362362         IF( lk_mpp    )   CALL mpp_sum( ierr ) 
    363          IF( ierr /= 0 )   CALL ctl_stop('STOP', 'angle_msh_geo: unable to allocate arrays' ) 
     363         IF( ierr /= 0 )   CALL ctl_stop('geo2oce: unable to allocate arrays' ) 
    364364      ENDIF 
    365365 
     
    438438      !!---------------------------------------------------------------------- 
    439439 
    440       IF( ALLOCATED( gsinlon ) ) THEN 
     440      IF( .NOT. ALLOCATED( gsinlon ) ) THEN 
    441441         ALLOCATE( gsinlon(jpi,jpj,4) , gcoslon(jpi,jpj,4) ,   & 
    442442            &      gsinlat(jpi,jpj,4) , gcoslat(jpi,jpj,4) , STAT=ierr ) 
    443443         IF( lk_mpp    )   CALL mpp_sum( ierr ) 
    444          IF( ierr /= 0 )   CALL ctl_stop('STOP', 'angle_msh_geo: unable to allocate arrays' ) 
     444         IF( ierr /= 0 )   CALL ctl_stop('oce2geo: unable to allocate arrays' ) 
    445445      ENDIF 
    446446 
  • branches/2013/dev_LOCEAN_2013/NEMOGCM/NEMO/OPA_SRC/SBC/sbccpl.F90

    r4161 r4162  
    373373      ! 
    374374      IF( TRIM( sn_rcv_tau%cldes ) /= 'oce and ice' ) THEN        ! 'oce and ice' case ocean stress on ocean mesh used 
    375          srcv(jpr_itz1:jpr_itz2)%laction = .FALSE.    ! ice components not received (itx1 and ity1 used later) 
     375         srcv(jpr_itx1:jpr_itz2)%laction = .FALSE.    ! ice components not received 
    376376         srcv(jpr_itx1)%clgrid = 'U'                  ! ocean stress used after its transformation 
    377377         srcv(jpr_ity1)%clgrid = 'V'                  ! i.e. it is always at U- & V-points for i- & j-comp. resp. 
     
    392392      SELECT CASE( TRIM( sn_rcv_emp%cldes ) ) 
    393393      CASE( 'oce only'      )   ;   srcv(                                 jpr_oemp   )%laction = .TRUE.  
    394       CASE( 'conservative'  )   ;   srcv( (/jpr_rain, jpr_snow, jpr_ievp, jpr_tevp/) )%laction = .TRUE. 
     394      CASE( 'conservative'  ) 
     395         srcv( (/jpr_rain, jpr_snow, jpr_ievp, jpr_tevp/) )%laction = .TRUE. 
     396         IF ( k_ice <= 1 )  srcv(jpr_ivep)%laction = .FALSE. 
    395397      CASE( 'oce and ice'   )   ;   srcv( (/jpr_ievp, jpr_sbpr, jpr_semp, jpr_oemp/) )%laction = .TRUE. 
    396398      CASE default              ;   CALL ctl_stop( 'sbc_cpl_init: wrong definition of sn_rcv_emp%cldes' ) 
     
    450452         CALL ctl_stop( 'sbc_cpl_init: namsbc_cpl namelist mismatch between sn_rcv_qns%cldes and sn_rcv_dqnsdt%cldes' ) 
    451453      !                                                      ! ------------------------- ! 
    452       !                                                      !    Ice Qsr penetration    !    
    453       !                                                      ! ------------------------- ! 
    454       ! fraction of net shortwave radiation which is not absorbed in the thin surface layer  
    455       ! and penetrates inside the ice cover ( Maykut and Untersteiner, 1971 ; Elbert anbd Curry, 1993 ) 
    456       ! Coupled case: since cloud cover is not received from atmosphere  
    457       !               ===> defined as constant value -> definition done in sbc_cpl_init 
    458       IF ( ALLOCATED (fr1_i0)) fr1_i0 (:,:) = 0.18 
    459       IF ( ALLOCATED (fr2_i0)) fr2_i0 (:,:) = 0.82 
    460       !                                                      ! ------------------------- ! 
    461454      !                                                      !      10m wind module      !    
    462455      !                                                      ! ------------------------- ! 
     
    493486      ! Allocate taum part of frcv which is used even when not received as coupling field 
    494487      IF ( .NOT. srcv(jpr_taum)%laction ) ALLOCATE( frcv(jpr_taum)%z3(jpi,jpj,srcv(jn)%nct) ) 
     488      ! Allocate itx1 and ity1 as they are used in sbc_cpl_ice_tau even if srcv(jpr_itx1)%laction = .FALSE. 
     489      IF( k_ice /= 0 ) THEN 
     490         IF ( .NOT. srcv(jpr_itx1)%laction ) ALLOCATE( frcv(jpr_itx1)%z3(jpi,jpj,srcv(jn)%nct) ) 
     491         IF ( .NOT. srcv(jpr_ity1)%laction ) ALLOCATE( frcv(jpr_ity1)%z3(jpi,jpj,srcv(jn)%nct) ) 
     492      END IF 
    495493 
    496494      ! ================================ ! 
     
    13161314      END SELECT 
    13171315 
     1316      !    Ice Qsr penetration used (only?)in lim2 or lim3  
     1317      ! fraction of net shortwave radiation which is not absorbed in the thin surface layer  
     1318      ! and penetrates inside the ice cover ( Maykut and Untersteiner, 1971 ; Elbert anbd Curry, 1993 ) 
     1319      ! Coupled case: since cloud cover is not received from atmosphere  
     1320      !               ===> defined as constant value -> definition done in sbc_cpl_init 
     1321      fr1_i0(:,:) = 0.18 
     1322      fr2_i0(:,:) = 0.82 
     1323 
     1324 
    13181325      CALL wrk_dealloc( jpi,jpj, zcptn, ztmp, zicefr ) 
    13191326      ! 
  • branches/2013/dev_LOCEAN_2013/NEMOGCM/NEMO/OPA_SRC/TRA/eosbn2.F90

    r4147 r4162  
    675675 
    676676 
    677    FUNCTION tfreez( psal ) RESULT( ptf ) 
     677   FUNCTION tfreez( psal, pdep ) RESULT( ptf ) 
    678678      !!---------------------------------------------------------------------- 
    679679      !!                 ***  ROUTINE eos_init  *** 
     
    688688      !!---------------------------------------------------------------------- 
    689689      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ) ::   psal   ! salinity             [psu] 
     690      REAL(wp), DIMENSION(jpi,jpj), INTENT(in   ), OPTIONAL ::   pdep   ! depth      [decibars] 
    690691      ! Leave result array automatic rather than making explicitly allocated 
    691692      REAL(wp), DIMENSION(jpi,jpj)                ::   ptf    ! freezing temperature [Celcius] 
     
    694695      ptf(:,:) = ( - 0.0575_wp + 1.710523e-3_wp * SQRT( psal(:,:) )   & 
    695696         &                     - 2.154996e-4_wp *       psal(:,:)   ) * psal(:,:) 
     697      IF ( PRESENT( pdep ) ) THEN    
     698         ptf(:,:) = ptf(:,:) - 7.53e-4_wp * pdep(:,:) 
     699      ENDIF 
    696700      ! 
    697701   END FUNCTION tfreez 
  • branches/2013/dev_LOCEAN_2013/NEMOGCM/NEMO/SAS_SRC/daymod.F90

    r3851 r4162  
    246246               nday_year = 1 
    247247               nsec_year = ndt05 
     248               IF( nsec1jan000 >= 2 * (2**30 - nsecd * nyear_len(1) / 2 ) ) THEN   ! test integer 4 max value 
     249                  CALL ctl_stop( 'The number of seconds between Jan. 1st 00h of nit000 year and Jan. 1st 00h ',   & 
     250                     &           'of the current year is exceeding the INTEGER 4 max VALUE: 2^31-1 -> 68.09 years in seconds', & 
     251                     & 'You must do a restart at higher frequency (or remove this STOP and recompile everything in I8)' ) 
     252               ENDIF 
    248253               nsec1jan000 = nsec1jan000 + nsecd * nyear_len(1) 
    249254               IF( nleapy == 1 )   CALL day_mth 
  • branches/2013/dev_LOCEAN_2013/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zsed.F90

    r4148 r4162  
    8282      IF( nn_timing == 1 )  CALL timing_start('p4z_sed') 
    8383      ! 
    84       IF( kt == nit000 .AND. jnt == 1 )  THEN 
     84      IF( kt == nittrc000 .AND. jnt == 1 )  THEN 
    8585         ryyss    = nyear_len(1) * rday    ! number of seconds per year and per month 
    8686         rmtss    = ryyss / raamo 
  • branches/2013/dev_LOCEAN_2013/NEMOGCM/NEMO/TOP_SRC/PISCES/P4Z/p4zsms.F90

    r4153 r4162  
    291291   END SUBROUTINE p4z_ph_ini 
    292292 
    293  
    294293   SUBROUTINE p4z_rst( kt, cdrw ) 
    295294      !!--------------------------------------------------------------------- 
     
    320319         ELSE 
    321320!            hi(:,:,:) = 1.e-9  
    322            CALL p4z_ph_ini 
     321            CALL p4z_ph_ini 
    323322         ENDIF 
    324323         CALL iom_get( numrtr, jpdom_autoglo, 'Silicalim', xksi(:,:) ) 
  • branches/2013/dev_LOCEAN_2013/NEMOGCM/NEMO/TOP_SRC/PISCES/trcini_pisces.F90

    r4152 r4162  
    160160         xksi(:,:)    = 2.e-6 
    161161         xksimax(:,:) = xksi(:,:) 
    162          ! 
    163162      END IF 
    164163 
  • branches/2013/dev_LOCEAN_2013/NEMOGCM/TOOLS/COMPILE/Fcheck_archfile.sh

    r4148 r4162  
    4040# :: 
    4141# 
    42 #  $ ./Fcheck_archfile.sh ARCHFILE COMPILER 
     42#  $ ./Fcheck_archfile.sh ARCHFILE CPPFILE COMPILER 
    4343# 
    4444# 
     
    9494   else 
    9595       if [ -f ${COMPIL_DIR}/$1 ]; then 
    96       # has the cpp keys file been changed since we copied the arch file in ${COMPIL_DIR}? 
    97       mycpp=$( ls -l ${COMPIL_DIR}/$2 | sed -e "s/.* -> //" ) 
    98       if [ "$mycpp" != "$( cat ${COMPIL_DIR}/cpp.history )" ]; then 
    99           echo $mycpp > ${COMPIL_DIR}/cpp.history 
    100           cpeval ${myarch} ${COMPIL_DIR}/$1 
     96      if [ "$2" != "nocpp" ]  
     97      then 
     98          # has the cpp keys file been changed since we copied the arch file in ${COMPIL_DIR}? 
     99          mycpp=$( ls -l ${COMPIL_DIR}/$2 | sed -e "s/.* -> //" ) 
     100          if [ "$mycpp" != "$( cat ${COMPIL_DIR}/cpp.history )" ]; then 
     101         echo $mycpp > ${COMPIL_DIR}/cpp.history 
     102         cpeval ${myarch} ${COMPIL_DIR}/$1 
     103          fi 
     104          # has the cpp keys file been updated since we copied the arch file in ${COMPIL_DIR}? 
     105          mycpp=$( find -L ${COMPIL_DIR} -cnewer ${COMPIL_DIR}/$1 -name $2 -print ) 
     106          [ ${#mycpp} -ne 0 ] && cpeval ${myarch} ${COMPIL_DIR}/$1 
    101107      fi 
    102       # has the cpp keys file been updated since we copied the arch file in ${COMPIL_DIR}? 
    103       mycpp=$( find -L ${COMPIL_DIR} -cnewer ${COMPIL_DIR}/$1 -name $2 -print ) 
    104       [ ${#mycpp} -ne 0 ] && cpeval ${myarch} ${COMPIL_DIR}/$1 
    105108      # has myarch file been updated since we copied it in ${COMPIL_DIR}? 
    106109      myarchdir=$( dirname ${myarch} ) 
     
    134137    if [ "$myarch" == "$( cat ${COMPIL_DIR}/arch.history )" ]; then  
    135138   if [ -f ${COMPIL_DIR}/$1 ]; then 
    136        # has the cpp keys file been changed since we copied the arch file in ${COMPIL_DIR}? 
    137        mycpp=$( ls -l ${COMPIL_DIR}/$2 | sed -e "s/.* -> //" ) 
    138        if [ "$mycpp" != "$( cat ${COMPIL_DIR}/cpp.history )" ]; then 
    139       echo $mycpp > ${COMPIL_DIR}/cpp.history 
    140       cpeval ${myarch} ${COMPIL_DIR}/$1 
     139       if [ "$2" != "nocpp" ]  
     140       then 
     141      # has the cpp keys file been changed since we copied the arch file in ${COMPIL_DIR}? 
     142      mycpp=$( ls -l ${COMPIL_DIR}/$2 | sed -e "s/.* -> //" ) 
     143      if [ "$mycpp" != "$( cat ${COMPIL_DIR}/cpp.history )" ]; then 
     144          echo $mycpp > ${COMPIL_DIR}/cpp.history 
     145          cpeval ${myarch} ${COMPIL_DIR}/$1 
     146      fi 
     147      # has the cpp keys file been updated since we copied the arch file in ${COMPIL_DIR}? 
     148      mycpp=$( find -L ${COMPIL_DIR} -cnewer ${COMPIL_DIR}/$1 -name $2 -print ) 
     149      [ ${#mycpp} -ne 0 ] && cpeval ${myarch} ${COMPIL_DIR}/$1 
    141150       fi 
    142        # has the cpp keys file been updated since we copied the arch file in ${COMPIL_DIR}? 
    143        mycpp=$( find -L ${COMPIL_DIR} -cnewer ${COMPIL_DIR}/$1 -name $2 -print ) 
    144        [ ${#mycpp} -ne 0 ] && cpeval ${myarch} ${COMPIL_DIR}/$1 
    145151       # has myarch file been updated since we copied it in ${COMPIL_DIR}? 
    146152       myarch=$( find -L ${MAIN_DIR}/ARCH -cnewer ${COMPIL_DIR}/$1 -name arch-${3}.fcm -print ) 
     
    150156   fi 
    151157    else 
    152    ls -l ${COMPIL_DIR}/$2 | sed -e "s/.* -> //" > ${COMPIL_DIR}/cpp.history 
     158   if [ "$2" != "nocpp" ]  
     159   then 
     160       ls -l ${COMPIL_DIR}/$2 | sed -e "s/.* -> //" > ${COMPIL_DIR}/cpp.history 
     161   fi 
    153162   echo ${myarch} > ${COMPIL_DIR}/arch.history 
    154163   cpeval ${myarch} ${COMPIL_DIR}/$1 
     
    157166 
    158167#- do we need xios library? 
    159 use_iom=$( sed -e "s/#.*$//" ${COMPIL_DIR}/$2 | grep -c key_iomput ) 
     168if [ "$2" != "nocpp" ]  
     169then 
     170    use_iom=$( sed -e "s/#.*$//" ${COMPIL_DIR}/$2 | grep -c key_iomput ) 
     171else 
     172    use_iom=0 
     173fi 
    160174have_lxios=$( sed -e "s/#.*$//" ${COMPIL_DIR}/$1 | grep -c "\-lxios" ) 
    161175if [[ ( $use_iom -eq 0 ) && ( $have_lxios -ge 1 ) ]] 
     
    166180 
    167181#- do we need oasis libraries? 
    168 use_oasis=$( sed -e "s/#.*$//" ${COMPIL_DIR}/$2 | grep -c key_oasis3 ) 
     182if [ "$2" != "nocpp" ]  
     183then 
     184    use_oasis=$( sed -e "s/#.*$//" ${COMPIL_DIR}/$2 | grep -c key_oasis3 ) 
     185else 
     186    use_oasis=0 
     187fi 
    169188for liboa in psmile.MPI1 mct mpeu scrip mpp_io 
    170189do 
  • branches/2013/dev_LOCEAN_2013/NEMOGCM/TOOLS/MISCELLANEOUS/chk_iomput.sh

    r4153 r4162  
    5959#------------------------------------------------ 
    6060# 
    61 external=$( grep -c "<field_definition.* src=" $xmlfile ) 
     61external=$( grep -c "<field_definition  *\([^ ].* \)*src=" $xmlfile ) 
    6262if [ $external -eq 1 ] 
    6363then 
    64     xmlfield_def=$( grep "<field_definition.* src=" $xmlfile | sed -e 's/.*src="\([^"]*\)".*/\1/' ) 
     64    xmlfield_def=$( grep "<field_definition  *\([^ ].* \)*src=" $xmlfile | sed -e 's/.*src="\([^"]*\)".*/\1/' ) 
    6565    xmlfield_def=$( dirname $xmlfile )/$xmlfield_def    
    6666else 
    6767    xmlfield_def=$xmlfile 
    6868fi 
    69 [ $inxml -eq 1 ] && grep "< *field * id *=" $xmlfield_def 
     69[ $inxml -eq 1 ] && grep "< *field  *\([^ ].* \)*id *=" $xmlfield_def 
    7070[ $insrc -eq 1 ] && find $srcdir -name "*.[Ffh]90" -exec grep -iH "^[^\!]*call  *iom_put *(" {} \; 
    7171[ $(( $insrc + $inxml )) -ge 1 ] && exit 
     
    9191# list of variables defined in the xml file 
    9292# 
    93 varlistxml=$( grep "< *field.* id *=" $xmlfield_def  | sed -e "s/^.*< *field.* id *= *[\"\']\([^\"\']*\)[\"\'].*/\1/" | sort -d ) 
     93varlistxml=$( grep "< *field  *\([^ ].* \)*id *=" $xmlfield_def  | sed -e "s/^.*< *field .*id *= *[\"\']\([^\"\']*\)[\"\'].*/\1/" | sort -d ) 
    9494# 
    9595# list of variables to be outputed in the xml file 
    9696# 
    97 varlistout=$( grep "< *field.* field_ref *=" $xmlfile  | sed -e "s/^.*< *field.* field_ref *= *[\"\']\([^\"\']*\)[\"\'].*/\1/" | sort -d ) 
     97varlistout=$( grep "< *field  *\([^ ].* \)*field_ref *=" $xmlfile  | sed -e "s/^.*< *field .*field_ref *= *[\"\']\([^\"\']*\)[\"\'].*/\1/" | sort -d ) 
    9898# 
    9999echo "--------------------------------------------------" 
  • branches/2013/dev_LOCEAN_2013/NEMOGCM/TOOLS/maketools

    r3294 r4162  
    146146 
    147147#- When used for the first time, choose a compiler --- 
    148 . ${COMPIL_DIR}/Fcheck_archfile.sh arch_tools.fcm ${CMP_NAM} || exit 
     148. ${COMPIL_DIR}/Fcheck_archfile.sh arch_tools.fcm nocpp ${CMP_NAM} || exit 
    149149 
    150150#- Choose a default tool if needed --- 
Note: See TracChangeset for help on using the changeset viewer.