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

Changeset 1818


Ignore:
Timestamp:
2010-03-25T15:13:55+01:00 (14 years ago)
Author:
rblod
Message:

Do the fixes on the right place e.g. the trunk

Location:
trunk/NEMO
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/LIM_SRC_2/limwri_2.F90

    r1715 r1818  
    313313      CALL histwrite( kid, "iicetemp", kt, sist(:,:) - rt0, jpi*jpj, (/1/) ) 
    314314      CALL histwrite( kid, "ioceflxb", kt, fbif           , jpi*jpj, (/1/) ) 
    315       CALL histwrite( kid, "iicevelv", kt, u_ice          , jpi*jpj, (/1/) ) 
    316       CALL histwrite( kid, "iicevelu", kt, v_ice          , jpi*jpj, (/1/) ) 
     315      CALL histwrite( kid, "iicevelu", kt, u_ice          , jpi*jpj, (/1/) ) 
     316      CALL histwrite( kid, "iicevelv", kt, v_ice          , jpi*jpj, (/1/) ) 
    317317      CALL histwrite( kid, "isstempe", kt, sst_m          , jpi*jpj, (/1/) ) 
    318318      CALL histwrite( kid, "isssalin", kt, sss_m          , jpi*jpj, (/1/) ) 
  • trunk/NEMO/OPA_SRC/DIA/diadimg.F90

    r1715 r1818  
    1010   USE dom_oce         ! ocean space and time domain 
    1111   USE in_out_manager  ! I/O manager 
     12   USE daymod          ! calendar 
    1213 
    1314   IMPLICIT NONE 
     
    2122   !!---------------------------------------------------------------------- 
    2223   !!   OPA 9.0 , LOCEAN-IPSL (2005)  
    23    !! $Id$  
     24   !! $Header$  
    2425   !! This software is governed by the CeCILL licence see modipsl/doc/NEMO_CeCILL.txt  
    2526   !!---------------------------------------------------------------------- 
     
    5657    INTEGER :: jk, jn           ! dummy loop indices 
    5758    INTEGER :: irecl4,             &    ! record length in bytes 
    58          &       inum,             &    ! logical unit 
    59          &       irec                   ! current record to be written 
     59         &       inum,             &    ! logical unit (set to 14) 
     60         &       irec,             &    ! current record to be written 
     61         &       irecend                ! record number where nclit... are stored 
    6062    REAL(sp)                    :: zdx,zdy,zspval,zwest,ztimm 
    6163    REAL(sp)                    :: zsouth 
     
    6971    !! * Initialisations 
    7072 
    71     irecl4 = MAX(jpi*jpj*sp , 84+18*sp + (jpk+8)*jpnij*sp ) 
     73    irecl4 = MAX(jpi*jpj*sp , 84+(18+1+jpk)*sp ) 
    7274 
    7375    zspval=0.0_sp    ! special values on land 
     
    101103 
    102104    IF ( ln_dimgnnn  ) THEN 
     105     irecl4 = MAX(jpi*jpj*sp , 84+(18+jpk)*sp + 8*jpnij*sp  ) 
    103106       WRITE(clname,'(a,a,i3.3)') TRIM(cd_name),'.',narea 
    104        CALL ctl_opn( inum, clname, 'REPLACE', 'UNFORMATTED', 'DIRECT', irecl4, numout, lwp ) 
     107       CALL ctl_opn(inum, clname,'UNKNOWN','UNFORMATTED','DIRECT',irecl4,numout,lwp) 
    105108       WRITE(inum,REC=1 ) clver, cd_text, irecl4, & 
    106109            &     jpi,jpj, klev, 1 , 1 ,            & 
     
    127130       ENDIF 
    128131    ELSE 
     132       clver='@!03'           ! dimg string identifier 
     133       ! note that version @!02 is optimized with respect to record length. 
     134       ! The vertical dep variable is reduced to klev instead of klev*jpnij : 
     135       !   this is OK for jpnij < 181 (jpk=46) 
     136       ! for more processors, irecl4 get huge and that's why we switch to '@!03': 
     137       !  In this case we just add an extra integer to the standard dimg structure, 
     138       !  which is a record number where the arrays nlci etc... starts (1 per record) 
     139        
    129140       !! Standard dimgproc (1 file per variable, all procs. write to this file ) 
    130141       !! * Open file 
    131        CALL ctl_opn( inum, cd_name, 'REPLACE', 'UNFORMATTED', 'DIRECT', irecl4, numout, lwp ) 
     142       CALL ctl_opn(inum, cd_name,'UNKNOWN','UNFORMATTED','DIRECT',irecl4,numout,lwp) 
    132143 
    133144       !! * Write header on record #1 
     145       irecend=1 + klev*jpnij  
    134146       IF(lwp) WRITE(inum,REC=1 ) clver, cd_text, irecl4, & 
    135             &     jpi,jpj, klev*jpnij, 1 , 1 ,            & 
     147            &     jpi,jpj, klev, 1 , 1 ,            & 
    136148            &     zwest, zsouth, zdx, zdy, zspval,  & 
    137             &     (z4dep(1:klev),jn=1,jpnij),       & 
     149            &     z4dep(1:klev),       & 
    138150            &     ztimm,                            & 
    139             &     narea, jpnij,jpiglo,jpjglo,jpizoom, jpjzoom,    &    ! extension to dimg for mpp output 
    140             &     nlcit,nlcjt, nldit, nldjt, nleit, nlejt, nimppt, njmppt  ! 
     151            &     narea, jpnij,jpiglo,jpjglo,jpizoom, jpjzoom, irecend  
     152       IF (lwp ) THEN 
     153         WRITE(inum,REC=irecend + 1 ) nlcit 
     154         WRITE(inum,REC=irecend + 2 ) nlcjt 
     155         WRITE(inum,REC=irecend + 3 ) nldit 
     156         WRITE(inum,REC=irecend + 4 ) nldjt 
     157         WRITE(inum,REC=irecend + 5 ) nleit 
     158         WRITE(inum,REC=irecend + 6 ) nlejt 
     159         WRITE(inum,REC=irecend + 7 ) nimppt 
     160         WRITE(inum,REC=irecend + 8 ) njmppt 
     161       ENDIF 
     162      !   &    ! extension to dimg for mpp output 
     163      !   &     nlcit,nlcjt, nldit, nldjt, nleit, nlejt, nimppt, njmppt  ! 
    141164 
    142165       !! * Write klev levels 
  • trunk/NEMO/OPA_SRC/OBC/obc_oce.F90

    r1601 r1818  
    2727   ! 
    2828   !                                  !!* Namelist namobc: open boundary condition * 
    29    INTEGER           ::   nn_nbobc    = 2        !: number of open boundaries ( 1=< nbobc =< 4 )  
    3029   INTEGER           ::   nn_obcdta   = 0        !:  = 0 use the initial state as obc data 
    3130   !                                             !   = 1 read obc data in obcxxx.dta files 
  • trunk/NEMO/OPA_SRC/OBC/obcini.F90

    r1633 r1818  
    7070 
    7171      ! convert DOCTOR namelist name into the OLD names 
    72       nbobc    = nn_nbobc 
    7372      nobc_dta = nn_obcdta 
    7473      cffile   = cn_obcdta 
     
    101100      IF(lwp) WRITE(numout,*) 'obc_init : initialization of open boundaries' 
    102101      IF(lwp) WRITE(numout,*) '~~~~~~~~' 
    103       IF(lwp) WRITE(numout,*) '   Number of open boundaries    nn_nbobc = ', nn_nbobc 
     102      IF(lwp) WRITE(numout,*) '   Number of open boundaries    nbobc = ', nbobc 
    104103      IF(lwp) WRITE(numout,*) 
    105104 
     
    306305      IF( lp_obc_east ) THEN 
    307306         !... (jpjed,jpjefm1),jpieob 
     307         bmask(nie0p1:nie1p1,nje0:nje1m1) = 0.e0 
    308308 
    309309         ! ... initilization to zero 
     
    341341      IF( lp_obc_north ) THEN 
    342342         ! ... jpjnob,(jpind,jpisfm1) 
     343         bmask(nin0:nin1m1,njn0p1:njn1p1) = 0.e0 
    343344 
    344345         ! ... initilization to zero 
     
    440441            END DO 
    441442         END IF 
    442    
     443 
    443444         IF( lp_obc_north ) THEN ! ... North open boundary lateral surface 
    444445            DO jj = njn0, njn1 
  • trunk/NEMO/OPA_SRC/OBC/obcrst.F90

    r1715 r1818  
    9696         ! ------------- 
    9797 
    98          CALL ctl_opn( inum, 'restart.obc.output', 'REPLACE', 'UNFORMATTED', 'DIRECT', nreclo, numout, lwp ) 
     98         CALL ctl_opn( inum, 'restart.obc.output', 'UNKNOWN', 'UNFORMATTED', 'DIRECT', nreclo, numout, lwp ) 
    9999  
    100100         ! 1.2 Write header 
     
    322322      ! 0.1 Open files 
    323323      ! --------------- 
    324       CALL ctl_opn( inum, 'restart.obc', 'REPLACE', 'UNFORMATTED', 'DIRECT', nreclo, numout, lwp ) 
     324      CALL ctl_opn( inum, 'restart.obc', 'UNKNOWN', 'UNFORMATTED', 'DIRECT', nreclo, numout, lwp ) 
    325325 
    326326      ! 1. Read 
  • trunk/NEMO/OPA_SRC/SBC/fldread.F90

    r1730 r1818  
    368368          
    369369         ! if previous year/month/day file does not exist, we switch to the current year/month/day 
    370          IF( llprev .AND. sdjf%num == 0 ) THEN 
     370         IF( llprev .AND. sdjf%num <= 0 ) THEN 
    371371            CALL ctl_warn( 'previous year/month/day file: '//TRIM(sdjf%clname)//' not present -> back to current year/month/day') 
    372372            ! we force to read the first record of the current year/month/day instead of last record of previous year/month/day 
     
    399399      ENDIF 
    400400 
    401       IF( sdjf%num == 0 )   CALL fld_clopn( sdjf, nyear, nmonth, nday )   ! make sure current year/month/day file is opened 
     401      IF( sdjf%num <= 0 )   CALL fld_clopn( sdjf, nyear, nmonth, nday )   ! make sure current year/month/day file is opened 
    402402 
    403403      sdjf%nswap_sec = nsec_year + nsec1jan000 - 1   ! force read/update the after data in the following part of fld_read  
Note: See TracChangeset for help on using the changeset viewer.