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

Changeset 544


Ignore:
Timestamp:
2006-10-20T16:23:21+02:00 (18 years ago)
Author:
opalod
Message:

nemo_v1_update_078:RB: finalization of IOM

Location:
trunk
Files:
7 added
5 deleted
7 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/LIM_SRC/limrst.F90

    r508 r544  
    3232   PUBLIC   lim_rst_read    ! routine called by ??? module 
    3333 
    34    LOGICAL, PUBLIC ::   lrst_ice         !: logical to control the oce restart write  
     34   LOGICAL, PUBLIC ::   lrst_ice         !: logical to control the ice restart write  
    3535   INTEGER, PUBLIC ::   numrir, numriw   !: logical unit for ice restart (read and write) 
    3636 
     
    4343CONTAINS 
    4444 
    45 # if ( defined key_mpp_mpi || defined key_mpp_shmem ) && defined key_dimgout 
    46    !!---------------------------------------------------------------------- 
    47    !!   'key_mpp_mpi'     OR     'key_mpp_shmem'              MPP computing 
    48    !!   'key_dimgout' :                    Direct access file (DIMG format) 
    49    !!---------------------------------------------------------------------- 
    50 #  include "limrst_dimg.h90" 
    51  
    52 # else 
    53    !!---------------------------------------------------------------------- 
    54    !!   Default option                                          NetCDF file 
    55    !!---------------------------------------------------------------------- 
    56  
    5745   SUBROUTINE lim_rst_opn( kt ) 
    5846      !!---------------------------------------------------------------------- 
     
    6957      IF( kt == nit000 )   lrst_ice = .FALSE. 
    7058       
    71       IF    ( kt == nitrst - 2*nfice + 1 .AND. lrst_ice ) THEN 
    72          CALL ctl_stop( 'lim_rst_opn: ice restart frequency must be larger than nfice' ) 
    73          numriw = 0 
    74       ELSEIF( kt == nitrst - 2*nfice + 1 .OR.  nitend - nit000 +1 < 2*nfice ) THEN 
    75          ! beware if model runs less than 2*nfice time step 
     59      IF( kt == nitrst - 2*nfice + 1 .OR.  nitend - nit000 + 1 <= nfice ) THEN 
     60         ! beware if model runs less than nfice + 1 time step 
    7661         ! beware of the format used to write kt (default is i8.8, that should be large enough) 
    7762         IF( nitrst > 1.0e9 ) THEN    
     
    8469         clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_restart_ice" 
    8570         IF(lwp) WRITE(numout,*) '             open ice restart.output NetCDF file: '//clname 
    86          CALL iom_open( clname, numriw, ldwrt = .TRUE. ) 
     71         CALL iom_open( clname, numriw, ldwrt = .TRUE., kiolib = jprstdimg ) 
    8772         lrst_ice = .TRUE. 
    8873      ENDIF 
     
    191176      ENDIF 
    192177 
    193       CALL iom_open ( 'restart_ice_in', numrir ) 
     178      CALL iom_open ( 'restart_ice_in', numrir, kiolib = jprstdimg ) 
    194179 
    195180      CALL iom_get( numrir, 'nfice' , zfice ) 
     
    265250   END SUBROUTINE lim_rst_read 
    266251 
    267 # endif 
    268  
    269252#else 
    270253   !!---------------------------------------------------------------------- 
  • trunk/NEMO/OPA_SRC/DOM/domwri.F90

    r526 r544  
    1414   USE dom_oce         ! ocean space and time domain 
    1515   USE in_out_manager 
     16   USE iom 
    1617 
    1718   IMPLICIT NONE 
     
    2728 
    2829CONTAINS 
    29  
    30 #if ( defined key_mpp_mpi || defined key_mpp_shmem ) && defined key_dimgout 
    31    !!---------------------------------------------------------------------- 
    32    !!   'key_mpp_mpi'     OR 
    33    !!   'key_mpp_shmem' 
    34    !!   'key_dimgout' :         each processor makes its own direct access file  
    35    !!                      use build_nc_meshmask off line to retrieve  
    36    !!                      a ioipsl compliant meshmask file 
    37    !!---------------------------------------------------------------------- 
    38 #  include "domwri_dimg.h90" 
    39  
    40 #else 
    41    !!---------------------------------------------------------------------- 
    42    !!   Default option :                                        NetCDF file 
    43    !!---------------------------------------------------------------------- 
    4430 
    4531   SUBROUTINE dom_wri 
     
    7157      !!   9.0  !  02-08  (G. Madec)  F90 and several file 
    7258      !!---------------------------------------------------------------------- 
    73       !! * Modules used 
    74       USE ioipsl 
    75  
    76       !! * Local declarations 
    77       INTEGER  ::                & !!! * temprary units for : 
    78          inum0 ,                 &  ! 'mesh_mask.nc' file 
    79          inum1 ,                 &  ! 'mesh.nc'      file 
    80          inum2 ,                 &  ! 'mask.nc'      file 
    81          inum3 ,                 &  ! 'mesh_hgr.nc'  file 
    82          inum4                      ! 'mesh_zgr.nc'  file 
    83       INTEGER  ::   itime           !  output from restini ??? 
    84       REAL(wp) ::   zdate0 
    85       REAL(wp), DIMENSION(jpi,jpj) ::   & 
    86          zprt                       ! temporary array for bathymetry  
    87  
    88       CHARACTER (len=21) ::      & 
    89          clnam0  ,   &  ! filename (mesh and mask informations) 
    90          clnam1  ,   &  ! filename (mesh informations) 
    91          clnam2  ,   &  ! filename (mask informations) 
    92          clnam3  ,   &  ! filename (horizontal mesh informations) 
    93          clnam4         ! filename (vertical   mesh informations) 
     59      INTEGER  ::   inum0   ! temprary units for 'mesh_mask.nc' file 
     60      INTEGER  ::   inum1   ! temprary units for 'mesh.nc'      file 
     61      INTEGER  ::   inum2   ! temprary units for 'mask.nc'      file 
     62      INTEGER  ::   inum3   ! temprary units for 'mesh_hgr.nc'  file 
     63      INTEGER  ::   inum4   ! temprary units for 'mesh_zgr.nc'  file 
     64      REAL(wp), DIMENSION(jpi,jpj) ::    zprt   ! temporary array for bathymetry  
     65      CHARACTER (len=21) ::   clnam0   ! filename (mesh and mask informations) 
     66      CHARACTER (len=21) ::   clnam1   ! filename (mesh informations) 
     67      CHARACTER (len=21) ::   clnam2   ! filename (mask informations) 
     68      CHARACTER (len=21) ::   clnam3   ! filename (horizontal mesh informations) 
     69      CHARACTER (len=21) ::   clnam4   ! filename (vertical   mesh informations) 
    9470      !!---------------------------------------------------------------------- 
    9571 
     
    10379       clnam3 = 'mesh_hgr'   ! filename (horizontal mesh informations) 
    10480       clnam4 = 'mesh_zgr'   ! filename (vertical   mesh informations) 
    105  
    106 #if defined key_agrif 
    107       IF ( .NOT. Agrif_Root() ) THEN 
    108          clnam0 = TRIM(Agrif_CFixed())//'_'//TRIM(clnam0) 
    109          clnam1 = TRIM(Agrif_CFixed())//'_'//TRIM(clnam1) 
    110          clnam2 = TRIM(Agrif_CFixed())//'_'//TRIM(clnam2) 
    111          clnam3 = TRIM(Agrif_CFixed())//'_'//TRIM(clnam3) 
    112          clnam4 = TRIM(Agrif_CFixed())//'_'//TRIM(clnam4) 
    113       ENDIF 
    114 #endif 
    115  
    116       CALL ymds2ju( 0, 1, 1, 0.e0, zdate0 )    ! calendar initialization 
    11781 
    11882!       note that mbathy has been modified in dommsk or in solver. 
     
    12791         CASE ( 1 )                            !  create 'mesh_mask.nc' file 
    12892            !                                  ! ============================ 
    129  
    13093            IF(lwp) WRITE(numout,*) '          one file in "mesh_mask.nc" ' 
    131             CALL restini( 'NONE', jpi   , jpj   , glamt, gphit,  &   ! create 'mesh_mask.nc' file 
    132             &             jpk   , gdept_0 , trim(clnam0)        ,  &   ! in unit inum0 
    133             &             itime , zdate0, rdt   , inum0 , domain_id=nidom ) 
     94            CALL iom_open( TRIM(clnam0), inum0, ldwrt = .TRUE., kiolib = jprstdimg ) 
    13495            inum2 = inum0                                            ! put all the informations 
    13596            inum3 = inum0                                            ! in unit inum0 
     
    140101            !                                  !         'mask.nc' files 
    141102            !                                  ! ============================ 
    142  
    143103            IF(lwp) WRITE(numout,*) '          two files in "mesh.nc" and "mask.nc" ' 
    144             CALL restini( 'NONE', jpi   , jpj   , glamt, gphit,  &   ! create 'mesh.nc' file  
    145             &             jpk   , gdept_0 , trim(clnam1)        ,  &   ! in unit inum1  
    146             &             itime , zdate0, rdt   , inum1, domain_id=nidom ) 
    147             CALL restini( 'NONE', jpi   , jpj   , glamt, gphit,  &   ! create 'mask.nc' file  
    148             &             jpk   , gdept_0 , trim(clnam2)        ,  &   ! in unit inum2  
    149             &             itime , zdate0, rdt   , inum2, domain_id=nidom ) 
     104            CALL iom_open( TRIM(clnam1), inum1, ldwrt = .TRUE., kiolib = jprstdimg ) 
     105            CALL iom_open( TRIM(clnam2), inum2, ldwrt = .TRUE., kiolib = jprstdimg ) 
    150106            inum3 = inum1                                            ! put mesh informations  
    151107            inum4 = inum1                                            ! in unit inum1  
    152  
    153108            !                                  ! ============================ 
    154109         CASE ( 3 )                            !  create 'mesh_hgr.nc' 
     
    156111            !                                  !         'mask.nc'     files 
    157112            !                                  ! ============================ 
    158  
    159113            IF(lwp) WRITE(numout,*) '          three files in "mesh_hgr.nc" , mesh_zgr.nc" and "mask.nc" ' 
    160             CALL restini( 'NONE', jpi   , jpj   , glamt, gphit,  &   ! create 'mesh_hgr.nc' file 
    161             &             jpk   , gdept_0 , trim(clnam3)        ,  &   ! in unit inum3 
    162             &             itime , zdate0, rdt   , inum3, domain_id=nidom ) 
    163             CALL restini( 'NONE', jpi   , jpj   , glamt, gphit,  &   ! create 'mesh_zgr.nc' file 
    164             &             jpk   , gdept_0 , trim(clnam4)        ,  &   ! in unit inum4 
    165             &             itime , zdate0, rdt   , inum4, domain_id=nidom ) 
    166             CALL restini( 'NONE', jpi   , jpj   , glamt, gphit,  &   ! create 'mask.nc' file 
    167             &             jpk   , gdept_0 , trim(clnam2)        ,  &   ! in unit inum2 
    168             &             itime , zdate0, rdt   , inum2, domain_id=nidom ) 
     114            CALL iom_open( TRIM(clnam2), inum2, ldwrt = .TRUE., kiolib = jprstdimg ) 
     115            CALL iom_open( TRIM(clnam3), inum3, ldwrt = .TRUE., kiolib = jprstdimg ) 
     116            CALL iom_open( TRIM(clnam4), inum4, ldwrt = .TRUE., kiolib = jprstdimg ) 
    169117 
    170118         END SELECT 
    171119 
    172120         !                                                         ! masks (inum2)  
    173          CALL restput( inum2, 'tmask', jpi, jpj, jpk, 0, tmask )  
    174          CALL restput( inum2, 'umask', jpi, jpj, jpk, 0, umask ) 
    175          CALL restput( inum2, 'vmask', jpi, jpj, jpk, 0, vmask ) 
    176          CALL restput( inum2, 'fmask', jpi, jpj, jpk, 0, fmask ) 
     121         CALL iom_rstput( 0, 0, inum2, 'tmask', tmask, ktype = jp_i1 )  
     122         CALL iom_rstput( 0, 0, inum2, 'umask', umask, ktype = jp_i1 ) 
     123         CALL iom_rstput( 0, 0, inum2, 'vmask', vmask, ktype = jp_i1 ) 
     124         CALL iom_rstput( 0, 0, inum2, 'fmask', fmask, ktype = jp_i1 ) 
    177125 
    178126         !                                                         ! horizontal mesh (inum3) 
    179          CALL restput( inum3, 'glamt', jpi, jpj, 1, 0, glamt )     !    ! latitude 
    180          CALL restput( inum3, 'glamu', jpi, jpj, 1, 0, glamu ) 
    181          CALL restput( inum3, 'glamv', jpi, jpj, 1, 0, glamv ) 
    182          CALL restput( inum3, 'glamf', jpi, jpj, 1, 0, glamf ) 
    183  
    184          CALL restput( inum3, 'gphit', jpi, jpj, 1, 0, gphit )     !    ! longitude 
    185          CALL restput( inum3, 'gphiu', jpi, jpj, 1, 0, gphiu ) 
    186          CALL restput( inum3, 'gphiv', jpi, jpj, 1, 0, gphiv ) 
    187          CALL restput( inum3, 'gphif', jpi, jpj, 1, 0, gphif ) 
    188  
    189          CALL restput( inum3, 'e1t', jpi, jpj, 1, 0, e1t )         !    ! e1 scale factors 
    190          CALL restput( inum3, 'e1u', jpi, jpj, 1, 0, e1u ) 
    191          CALL restput( inum3, 'e1v', jpi, jpj, 1, 0, e1v ) 
    192          CALL restput( inum3, 'e1f', jpi, jpj, 1, 0, e1f ) 
    193  
    194          CALL restput( inum3, 'e2t', jpi, jpj, 1, 0, e2t )         !    ! e2 scale factors 
    195          CALL restput( inum3, 'e2u', jpi, jpj, 1, 0, e2u ) 
    196          CALL restput( inum3, 'e2v', jpi, jpj, 1, 0, e2v ) 
    197          CALL restput( inum3, 'e2f', jpi, jpj, 1, 0, e2f ) 
    198  
    199          CALL restput( inum3, 'ff', jpi, jpj, 1, 0, ff )           !    ! coriolis factor 
    200  
    201          CALL restput( inum4, 'mbathy', jpi, jpj, 1, 0, zprt ) 
     127         CALL iom_rstput( 0, 0, inum3, 'glamt', glamt, ktype = jp_r4 )     !    ! latitude 
     128         CALL iom_rstput( 0, 0, inum3, 'glamu', glamu, ktype = jp_r4 ) 
     129         CALL iom_rstput( 0, 0, inum3, 'glamv', glamv, ktype = jp_r4 ) 
     130         CALL iom_rstput( 0, 0, inum3, 'glamf', glamf, ktype = jp_r4 ) 
     131 
     132         CALL iom_rstput( 0, 0, inum3, 'gphit', gphit, ktype = jp_r4 )     !    ! longitude 
     133         CALL iom_rstput( 0, 0, inum3, 'gphiu', gphiu, ktype = jp_r4 ) 
     134         CALL iom_rstput( 0, 0, inum3, 'gphiv', gphiv, ktype = jp_r4 ) 
     135         CALL iom_rstput( 0, 0, inum3, 'gphif', gphif, ktype = jp_r4 ) 
     136 
     137         CALL iom_rstput( 0, 0, inum3, 'e1t', e1t, ktype = jp_r8 )         !    ! e1 scale factors 
     138         CALL iom_rstput( 0, 0, inum3, 'e1u', e1u, ktype = jp_r8 ) 
     139         CALL iom_rstput( 0, 0, inum3, 'e1v', e1v, ktype = jp_r8 ) 
     140         CALL iom_rstput( 0, 0, inum3, 'e1f', e1f, ktype = jp_r8 ) 
     141 
     142         CALL iom_rstput( 0, 0, inum3, 'e2t', e2t, ktype = jp_r8 )         !    ! e2 scale factors 
     143         CALL iom_rstput( 0, 0, inum3, 'e2u', e2u, ktype = jp_r8 ) 
     144         CALL iom_rstput( 0, 0, inum3, 'e2v', e2v, ktype = jp_r8 ) 
     145         CALL iom_rstput( 0, 0, inum3, 'e2f', e2f, ktype = jp_r8 ) 
     146 
     147         CALL iom_rstput( 0, 0, inum3, 'ff', ff, ktype = jp_r8 )           !    ! coriolis factor 
     148 
     149         CALL iom_rstput( 0, 0, inum4, 'mbathy', zprt, ktype = jp_i2 ) 
    202150 
    203151#if ! defined key_zco 
    204152         IF( ln_sco ) THEN                                         ! s-coordinate 
    205             CALL restput( inum4, 'hbatt', jpi, jpj, 1, 0, hbatt )      !    ! depth 
    206             CALL restput( inum4, 'hbatu', jpi, jpj, 1, 0, hbatu )  
    207             CALL restput( inum4, 'hbatv', jpi, jpj, 1, 0, hbatv ) 
    208             CALL restput( inum4, 'hbatf', jpi, jpj, 1, 0, hbatf ) 
     153            CALL iom_rstput( 0, 0, inum4, 'hbatt', hbatt )      !    ! depth 
     154            CALL iom_rstput( 0, 0, inum4, 'hbatu', hbatu )  
     155            CALL iom_rstput( 0, 0, inum4, 'hbatv', hbatv ) 
     156            CALL iom_rstput( 0, 0, inum4, 'hbatf', hbatf ) 
    209157    
    210             CALL restput( inum4, 'gsigt', 1, 1, jpk, 0, gsigt )        !    ! scaling coef. 
    211             CALL restput( inum4, 'gsigw', 1, 1, jpk, 0, gsigw )   
    212             CALL restput( inum4, 'gsi3w', 1, 1, jpk, 0, gsi3w ) 
    213             CALL restput( inum4, 'esigt', 1, 1, jpk, 0, esigt ) 
    214             CALL restput( inum4, 'esigw', 1, 1, jpk, 0, esigw ) 
    215  
    216             CALL restput( inum4, 'e3t', jpi, jpj, jpk, 0, e3t )       !    ! scale factors 
    217             CALL restput( inum4, 'e3u', jpi, jpj, jpk, 0, e3u ) 
    218             CALL restput( inum4, 'e3v', jpi, jpj, jpk, 0, e3v ) 
    219             CALL restput( inum4, 'e3w', jpi, jpj, jpk, 0, e3w ) 
    220  
    221             CALL restput( inum4, 'gdept_0' , 1, 1, jpk, 0, gdept_0 )  !    ! stretched system 
    222             CALL restput( inum4, 'gdepw_0' , 1, 1, jpk, 0, gdepw_0 ) 
     158            CALL iom_rstput( 0, 0, inum4, 'gsigt', gsigt )        !    ! scaling coef. 
     159            CALL iom_rstput( 0, 0, inum4, 'gsigw', gsigw )   
     160            CALL iom_rstput( 0, 0, inum4, 'gsi3w', gsi3w ) 
     161            CALL iom_rstput( 0, 0, inum4, 'esigt', esigt ) 
     162            CALL iom_rstput( 0, 0, inum4, 'esigw', esigw ) 
     163 
     164            CALL iom_rstput( 0, 0, inum4, 'e3t', e3t )       !    ! scale factors 
     165            CALL iom_rstput( 0, 0, inum4, 'e3u', e3u ) 
     166            CALL iom_rstput( 0, 0, inum4, 'e3v', e3v ) 
     167            CALL iom_rstput( 0, 0, inum4, 'e3w', e3w ) 
     168 
     169            CALL iom_rstput( 0, 0, inum4, 'gdept_0' , gdept_0 )  !    ! stretched system 
     170            CALL iom_rstput( 0, 0, inum4, 'gdepw_0' , gdepw_0 ) 
    223171         ENDIF 
    224172 
    225173         IF( ln_zps ) THEN                                         ! z-coordinate - partial steps 
    226             CALL restput( inum4, 'hdept' , jpi, jpj, 1, 0, hdept  )    !    ! depth 
    227             CALL restput( inum4, 'hdepw' , jpi, jpj, 1, 0, hdepw  )  
    228  
    229             CALL restput( inum4, 'e3t' , jpi, jpj, jpk, 0, e3t )      !    ! scale factors 
    230             CALL restput( inum4, 'e3u' , jpi, jpj, jpk, 0, e3u ) 
    231             CALL restput( inum4, 'e3v' , jpi, jpj, jpk, 0, e3v ) 
    232             CALL restput( inum4, 'e3w' , jpi, jpj, jpk, 0, e3w ) 
    233  
    234             CALL restput( inum4, 'gdept_0', 1, 1, jpk, 0, gdept_0 )   !    ! reference z-coord. 
    235             CALL restput( inum4, 'gdepw_0', 1, 1, jpk, 0, gdepw_0 ) 
    236             CALL restput( inum4, 'e3t_0'  , 1, 1, jpk, 0, e3t_0   ) 
    237             CALL restput( inum4, 'e3w_0'  , 1, 1, jpk, 0, e3w_0   ) 
     174            CALL iom_rstput( 0, 0, inum4, 'hdept' , hdept  )    !    ! depth 
     175            CALL iom_rstput( 0, 0, inum4, 'hdepw' , hdepw  )  
     176 
     177            CALL iom_rstput( 0, 0, inum4, 'e3t' , e3t )      !    ! scale factors 
     178            CALL iom_rstput( 0, 0, inum4, 'e3u' , e3u ) 
     179            CALL iom_rstput( 0, 0, inum4, 'e3v' , e3v ) 
     180            CALL iom_rstput( 0, 0, inum4, 'e3w' , e3w ) 
     181 
     182            CALL iom_rstput( 0, 0, inum4, 'gdept_0', gdept_0 )   !    ! reference z-coord. 
     183            CALL iom_rstput( 0, 0, inum4, 'gdepw_0', gdepw_0 ) 
     184            CALL iom_rstput( 0, 0, inum4, 'e3t_0'  , e3t_0   ) 
     185            CALL iom_rstput( 0, 0, inum4, 'e3w_0'  , e3w_0   ) 
    238186         ENDIF 
    239187 
     
    242190         IF( ln_zco ) THEN 
    243191         !                                                         ! z-coordinate - full steps 
    244             CALL restput( inum4, 'gdept_0', 1, 1, jpk, 0, gdept_0 )   !    ! depth 
    245             CALL restput( inum4, 'gdepw_0', 1, 1, jpk, 0, gdepw_0 ) 
    246             CALL restput( inum4, 'e3t_0'  , 1, 1, jpk, 0, e3t_0   )   !    ! scale factors 
    247             CALL restput( inum4, 'e3w_0'  , 1, 1, jpk, 0, e3w_0   ) 
     192            CALL iom_rstput( 0, 0, inum4, 'gdept_0', gdept_0 )   !    ! depth 
     193            CALL iom_rstput( 0, 0, inum4, 'gdepw_0', gdepw_0 ) 
     194            CALL iom_rstput( 0, 0, inum4, 'e3t_0'  , e3t_0   )   !    ! scale factors 
     195            CALL iom_rstput( 0, 0, inum4, 'e3w_0'  , e3w_0   ) 
    248196         ENDIF 
    249  
    250197         !                                     ! ============================ 
    251198         !                                     !        close the files  
     
    253200         SELECT CASE ( nmsh ) 
    254201            CASE ( 1 )                 
    255                CALL restclo( inum0 ) 
     202               CALL iom_close( inum0 ) 
    256203            CASE ( 2 ) 
    257                CALL restclo( inum1 ) 
    258                CALL restclo( inum2 ) 
     204               CALL iom_close( inum1 ) 
     205               CALL iom_close( inum2 ) 
    259206            CASE ( 3 ) 
    260                CALL restclo( inum2 ) 
    261                CALL restclo( inum3 ) 
    262                CALL restclo( inum4 ) 
     207               CALL iom_close( inum2 ) 
     208               CALL iom_close( inum3 ) 
     209               CALL iom_close( inum4 ) 
    263210         END SELECT 
    264211 
    265212   END SUBROUTINE dom_wri 
    266  
    267 #endif 
    268213 
    269214   !!====================================================================== 
  • trunk/NEMO/OPA_SRC/istate.F90

    r508 r544  
    3636   USE in_out_manager  ! I/O manager 
    3737   USE iom 
     38   USE ini1d           ! re-initialization of u-v mask for the 1D configuration 
     39   USE zpshde          ! partial step: hor. derivative (zps_hde routine) 
     40   USE eosbn2          ! equation of state            (eos bn2 routine) 
    3841    
    3942   IMPLICIT NONE 
     
    5962      !! ** Purpose :   Initialization of the dynamics and tracer fields. 
    6063      !!---------------------------------------------------------------------- 
     64      USE eosbn2          ! eq. of state, Brunt Vaisala frequency (eos     routine) 
    6165 
    6266      IF(lwp) WRITE(numout,*) 
     
    113117         ENDIF 
    114118 
     119         CALL eos( tb, sb, rhd, rhop )        ! before potential and in situ densities 
     120          
     121         IF( ln_zps .AND. .NOT. lk_cfg_1d )   & 
     122            &             CALL zps_hde( nit000, tb, sb, rhd,  &  ! Partial steps: before Horizontal DErivative 
     123            &                                  gtu, gsu, gru, &  ! of t, s, rd at the bottom ocean level 
     124            &                                  gtv, gsv, grv ) 
     125          
    115126      ENDIF 
     127 
     128 
    116129      !                                       ! Vertical velocity 
    117130      !                                       ! ----------------- 
     
    430443      !!                 p=integral [ rau*g dz ] 
    431444      !!---------------------------------------------------------------------- 
    432       USE eosbn2          ! eq. of state, Brunt Vaisala frequency (eos     routine) 
    433445      USE dynspg          ! surface pressure gradient             (dyn_spg routine) 
    434446      USE divcur          ! hor. divergence & rel. vorticity      (div_cur routine) 
  • trunk/NEMO/OPA_SRC/oce.F90

    r467 r544  
    2121   !! --------------------------- 
    2222   LOGICAL, PUBLIC ::   ln_dynhpg_imp   = .FALSE.  !: semi-implicite hpg flag 
     23   INTEGER, PUBLIC ::   nn_dynhpg_rst   = 0        !: add dynhpg implicit variables in restart ot not 
    2324 
    2425   !! dynamics and tracer fields 
  • trunk/NEMO/OPA_SRC/opa.F90

    r532 r544  
    349349      !! * Local declarations 
    350350 
    351       NAMELIST/namflg/ ln_dynhpg_imp 
     351      NAMELIST/namflg/ ln_dynhpg_imp, nn_dynhpg_rst 
    352352      !!---------------------------------------------------------------------- 
    353353 
     
    449449         WRITE(numout,*) '             centered (F) or semi-implicit (T)   ln_dynhpg_imp = ', ln_dynhpg_imp 
    450450         WRITE(numout,*) '             hydrostatic pressure gradient' 
    451       ENDIF 
     451         WRITE(numout,*) '             add dynhpg implicit variable        nn_dynhpg_rst = ', nn_dynhpg_rst 
     452         WRITE(numout,*) '             in restart ot not nn_dynhpg_rst' 
     453      ENDIF 
     454      IF( .NOT. ln_dynhpg_imp )   nn_dynhpg_rst = 0      ! force no adding dynhpg implicit variables in restart 
    452455 
    453456   END SUBROUTINE opa_flg 
  • trunk/NEMO/OPA_SRC/restart.F90

    r521 r544  
    2525   USE iom             ! I/O module 
    2626   USE trdmld_oce      ! ! ocean active mixed layer tracers trends variables 
     27   USE ini1d           ! re-initialization of u-v mask for the 1D configuration 
     28   USE zpshde          ! partial step: hor. derivative (zps_hde routine) 
     29   USE eosbn2          ! equation of state            (eos bn2 routine) 
    2730 
    2831   IMPLICIT NONE 
     
    8285         clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_restart" 
    8386         IF(lwp) WRITE(numout,*) '             open ocean restart.output NetCDF file: '//clname 
    84          CALL iom_open( clname, numrow, ldwrt = .TRUE. ) 
     87         CALL iom_open( clname, numrow, ldwrt = .TRUE., kiolib = jprstdimg ) 
    8588         IF( lk_trdmld )   THEN 
    8689            clname = TRIM(cexper)//"_"//TRIM(ADJUSTL(clkt))//"_restart_mld" 
    8790            IF(lwp) WRITE(numout,*) '             open ocean restart_mld NetCDF file: '//clname 
    88             CALL iom_open( clname, nummldw, ldwrt = .TRUE. ) 
     91            CALL iom_open( clname, nummldw, ldwrt = .TRUE., kiolib = jprstdimg ) 
    8992         ENDIF 
    9093         lrst_oce = .TRUE. 
     
    9396   END SUBROUTINE rst_opn 
    9497 
    95  
    96 #if  ( defined key_mpp_mpi   ||   defined key_mpp_shmem ) && defined key_dimgout 
    97    !!---------------------------------------------------------------------- 
    98    !!   'key_mpp_mpi'     OR      MPI massively parallel processing library 
    99    !!   'key_mpp_shmem'         SHMEM massively parallel processing library 
    100    !!                     AND 
    101    !!   'key_dimgout'           
    102    !!---------------------------------------------------------------------- 
    103    !!                 direct acces file one per processor 
    104    !!          (merging/splitting is done off-line, eventually) 
    105    !!----------------------------------------------------------------------- 
    106 #  include "restart_dimg.h90" 
    107  
    108 #else 
    109    !!---------------------------------------------------------------------- 
    110    !!   Default option                                          NetCDF file 
    111    !!---------------------------------------------------------------------- 
    11298 
    11399   SUBROUTINE rst_write( kt ) 
     
    128114         WRITE(numout,*) '~~~~~~~~~' 
    129115      ENDIF 
    130        
     116 
    131117      ! calendar control 
    132118      CALL iom_rstput( kt, nitrst, numrow, 'kt'     , REAL( kt    , wp) )   ! time-step  
    133119      CALL iom_rstput( kt, nitrst, numrow, 'ndastp' , REAL( ndastp, wp) )   ! date 
    134       CALL iom_rstput( kt, nitrst, numrow, 'adatrj' ,       adatrj      )   ! number of elapsed days since 
     120      CALL iom_rstput( kt, nitrst, numrow, 'adatrj' , adatrj            )   ! number of elapsed days since 
    135121      !                                                                     ! the begining of the run [s] 
     122      CALL iom_rstput( kt, nitrst, numrow, 'rdt'    , rdt               )   ! dynamics time step 
     123      CALL iom_rstput( kt, nitrst, numrow, 'rdttra1', rdttra(1)         )   ! surface tracer time step 
    136124 
    137125      ! prognostic variables 
     
    148136      CALL iom_rstput( kt, nitrst, numrow, 'rotn'   , rotn    ) 
    149137      CALL iom_rstput( kt, nitrst, numrow, 'hdivn'  , hdivn   ) 
    150  
    151 # if defined key_ice_lim         
     138       
     139#if defined key_ice_lim         
    152140      CALL iom_rstput( kt, nitrst, numrow, 'nfice'  , REAL( nfice, wp) )   !  ice computation frequency 
    153141      CALL iom_rstput( kt, nitrst, numrow, 'sst_io' , sst_io  ) 
     
    155143      CALL iom_rstput( kt, nitrst, numrow, 'u_io'   , u_io    ) 
    156144      CALL iom_rstput( kt, nitrst, numrow, 'v_io'   , v_io    ) 
    157 #  if defined key_coupled 
     145# if defined key_coupled 
    158146      CALL iom_rstput( kt, nitrst, numrow, 'alb_ice', alb_ice ) 
    159 #  endif 
    160147# endif 
    161 # if defined key_flx_bulk_monthly || defined key_flx_bulk_daily 
     148#endif 
     149#if defined key_flx_bulk_monthly || defined key_flx_bulk_daily 
    162150      CALL iom_rstput( kt, nitrst, numrow, 'nfbulk' , REAL( nfbulk, wp) )   !  bulk computation frequency 
    163151      CALL iom_rstput( kt, nitrst, numrow, 'gsst'   , gsst    ) 
    164 # endif 
     152#endif 
     153 
     154      IF( nn_dynhpg_rst == 1 ) THEN 
     155         CALL iom_rstput( kt, nitrst, numrow, 'rhd' , rhd  ) 
     156         CALL iom_rstput( kt, nitrst, numrow, 'rhop', rhop ) 
     157         IF( ln_zps ) THEN 
     158            CALL iom_rstput( kt, nitrst, numrow, 'gtu' , gtu ) 
     159            CALL iom_rstput( kt, nitrst, numrow, 'gsu' , gsu ) 
     160            CALL iom_rstput( kt, nitrst, numrow, 'gru' , gru ) 
     161            CALL iom_rstput( kt, nitrst, numrow, 'gtv' , gtv ) 
     162            CALL iom_rstput( kt, nitrst, numrow, 'gsv' , gsv ) 
     163            CALL iom_rstput( kt, nitrst, numrow, 'grv' , grv ) 
     164         ENDIF 
     165      ENDIF 
    165166 
    166167      IF( kt == nitrst ) THEN 
     
    201202      !!                    has been stored in the restart file. 
    202203      !!---------------------------------------------------------------------- 
    203       REAL(wp) ::   zcoef, zkt, zndastp, znfice, znfbulk 
    204 # if defined key_ice_lim 
     204      REAL(wp) ::   zcoef, zkt, zrdt, zrdttra1, zndastp, znfice, znfbulk 
     205#if defined key_ice_lim 
    205206      INTEGER  ::   ji, jj 
    206 # endif 
     207#endif 
    207208      !!---------------------------------------------------------------------- 
    208209 
     
    214215         WRITE(numout,*) ' *** Info on the present job : ' 
    215216         WRITE(numout,*) '   time-step           : ', nit000 
    216 !!$         WRITE(numout,*) '   solver type         : ', nsolv 
    217 !!$         IF( lk_zdftke ) THEN 
    218 !!$            WRITE(numout,*) '   tke option          : 1 ' 
    219 !!$         ELSE 
    220 !!$            WRITE(numout,*) '   tke option          : 0 ' 
    221 !!$         ENDIF 
    222217         WRITE(numout,*) '   date ndastp         : ', ndastp 
    223218         WRITE(numout,*) 
     
    237232      ENDIF 
    238233 
    239       CALL iom_open( 'restart', numror )                       ! Open 
     234      CALL iom_open( 'restart', numror, kiolib = jprstdimg )   ! Open 
    240235 
    241236      ! Calendar informations 
    242       CALL iom_get( numror, 'kt'    , zkt     )   ! time-step  
    243       CALL iom_get( numror, 'ndastp', zndastp )   ! date 
    244       ! Additional contol prints 
     237      CALL iom_get( numror, 'kt'     , zkt      )   ! time-step  
     238      CALL iom_get( numror, 'ndastp' , zndastp  )   ! date 
    245239      IF(lwp) THEN 
    246240         WRITE(numout,*) 
    247241         WRITE(numout,*) ' *** Info on the restart file read : ' 
    248242         WRITE(numout,*) '   time-step           : ', NINT( zkt ) 
    249 !!$         WRITE(numout,*) '   solver type         : ', +++ 
    250 !!$         WRITE(numout,*) '   tke option          : ', +++ 
    251243         WRITE(numout,*) '   date ndastp         : ', NINT( zndastp ) 
    252244         WRITE(numout,*) 
     
    259251      adatrj0 = ( REAL( nit000-1, wp ) * rdttra(1) ) / rday 
    260252      IF ( nrstdt == 2 ) THEN 
    261 !                            by default ndatsp has been set to ndate0 in dom_nam 
    262 !                            ndate0 has been read in the namelist (standard OPA 8) 
    263 !                            here when nrstdt=2 we keep the  final date of previous run 
     253         ! by default ndatsp has been set to ndate0 in dom_nam 
     254         ! ndate0 has been read in the namelist (standard OPA 8) 
     255         ! here when nrstdt=2 we keep the  final date of previous run 
    264256         ndastp = NINT( zndastp ) 
    265         CALL iom_get( numror, 'adatrj', adatrj )   ! number of elapsed days since the begining of last run 
    266       ENDIF 
    267  
     257         CALL iom_get( numror, 'adatrj', adatrj )   ! number of elapsed days since the begining of last run 
     258      ENDIF 
     259      ! Check dynamics and tracer time-step consistency and force Euler restart if changed 
     260      IF( iom_varid( numror, 'rdt' ) > 0 )   THEN 
     261         CALL iom_get( numror, 'rdt', zrdt ) 
     262         IF( zrdt /= rdt )   neuler = 0 
     263      ENDIF 
     264      IF( iom_varid( numror, 'rdttra1' ) > 0 )   THEN 
     265         CALL iom_get( numror, 'rdttra1', zrdttra1 ) 
     266         IF( zrdttra1 /= rdttra(1) )   neuler = 0 
     267      ENDIF 
     268      ! 
    268269      !                                                       ! Read prognostic variables 
    269270      CALL iom_get( numror, jpdom_local, 'ub'   , ub    )        ! before i-component velocity 
     
    292293      !!sm: TO BE MOVED IN NEW SURFACE MODULE... 
    293294 
    294 # if defined key_ice_lim 
     295#if defined key_ice_lim 
    295296      ! Louvain La Neuve Sea Ice Model 
    296297      IF( iom_varid( numror, 'nfice' ) > 0 ) then  
     
    300301         CALL iom_get( numror, jpdom_local, 'u_io'   , u_io    ) 
    301302         CALL iom_get( numror, jpdom_local, 'v_io'   , v_io    ) 
    302 #if defined key_coupled 
     303# if defined key_coupled 
    303304         CALL iom_get( numror, jpdom_local, 'alb_ice', alb_ice ) 
    304 #endif 
     305# endif 
    305306         IF( znfice /= REAL( nfice, wp ) ) THEN      ! if nfice changed between 2 runs 
    306307            zcoef = REAL( nfice-1, wp ) / znfice 
     
    324325            END DO 
    325326         END DO 
    326 #    if defined key_coupled 
     327# if defined key_coupled 
    327328         alb_ice(:,:) = 0.8 * tmask(:,:,1) 
    328 #    endif 
    329       ENDIF 
    330329# endif 
    331 # if defined key_flx_bulk_monthly || defined key_flx_bulk_daily 
     330      ENDIF 
     331#endif 
     332#if defined key_flx_bulk_monthly || defined key_flx_bulk_daily 
    332333      ! Louvain La Neuve Sea Ice Model 
    333334      IF( iom_varid( numror, 'nfbulk' ) > 0 ) THEN  
     
    344345         gsst(:,:) = REAL( nfbulk - 1, wp )*( tn(:,:,1) + rt0 ) 
    345346      ENDIF 
    346 # endif 
     347#endif 
    347348       
    348349      !!sm: end of TO BE MOVED IN NEW SURFACE MODULE... 
     350 
     351      IF( iom_varid( numror, 'rhd' ) > 0 ) THEN 
     352         CALL iom_get( numror, jpdom_local, 'rhd' , rhd  ) 
     353         CALL iom_get( numror, jpdom_local, 'rhop', rhop ) 
     354      ELSE 
     355         CALL eos( tb, sb, rhd, rhop )        ! before potential and in situ densities 
     356      ENDIF 
     357      IF( ln_zps .AND. .NOT. lk_cfg_1d ) THEN 
     358         IF( iom_varid( numror, 'gtu' ) > 0 ) THEN 
     359            CALL iom_get( numror, jpdom_local, 'gtu' , gtu ) 
     360            CALL iom_get( numror, jpdom_local, 'gsu' , gsu ) 
     361            CALL iom_get( numror, jpdom_local, 'gru' , gru ) 
     362            CALL iom_get( numror, jpdom_local, 'gtv' , gtv ) 
     363            CALL iom_get( numror, jpdom_local, 'gsv' , gsv ) 
     364            CALL iom_get( numror, jpdom_local, 'grv' , grv ) 
     365         ELSE 
     366            CALL zps_hde( nit000, tb , sb , rhd,   &  ! Partial steps: before Horizontal DErivative 
     367               &                  gtu, gsu, gru,   &  ! of t, s, rd at the bottom ocean level 
     368               &                  gtv, gsv, grv ) 
     369         ENDIF 
     370      ENDIF 
    349371      ! 
    350372   END SUBROUTINE rst_read 
    351373 
    352 #endif 
    353374 
    354375   !!===================================================================== 
  • trunk/UTIL/fait_AA_make

    r510 r544  
    253253echo 'TMP = ../../../tmp' 
    254254echo '#-Q- sxnec  # Compiler options for NEMO (IDRIS SX5-NEC) ' 
    255 echo '#-Q- sxnec  F_O = -dw -Wf\"-A idbl4\" -sx5 -C vopt -Wf"-init stack=nan" -Wl"-f nan" -Wf"-P nh" -Wf,-pvctl noassume loopcnt=10000 -L transform -I $(MODDIR) -I $(MODDIR)/oce' 
     255echo '#-Q- sxnec  F_O = -dw -Wf\"-A idbl4\" -sx5 -C vopt -Wf"-init stack=nan" -Wl"-f nan" -Wf"-P nh" -Wf,-pvctl noassume loopcnt=10000 -L transform -I $(MODDIR) -I $(MODDIR)/oce -I $(NCDF_INC)' 
    256256echo '#-Q- sxnec  F_F = $(F_O)' 
    257257echo '#-Q- sxnec  L_X = $(L_O)' 
    258258echo '#-Q- sx6nec  # Compiler options NEMO (CEA SX6-NEC) ' 
    259 echo '#-Q- sx6nec  F_O = -size_t64 -dw -Wf\"-A dbl4\" -sx6 -C vopt -Wf"-P nh" -Wf',-pvctl noassume loopcnt=10000 -L transform' -I $(MODDIR) -I $(MODDIR)/oce' 
    260 echo '#-Q- sx6nec  F_O = -size_t64 -dw -Wf\"-A dbl4\" -sx6 -ftrace -C vopt -Wf"-init stack=nan" -Wl"-f nan" -Wf"-P nh" -Wf,-pvctl noassume loopcnt=10000 -L transform -I $(MODDIR) -I $(MODDIR)/oce' 
     259echo '#-Q- sx6nec  F_O = -size_t64 -dw -Wf\"-A dbl4\" -sx6 -C vopt -Wf"-P nh" -Wf',-pvctl noassume loopcnt=10000 -L transform' -I $(MODDIR) -I $(MODDIR)/oce -I $(NCDF_INC)' 
     260echo '#-Q- sx6nec  F_O = -size_t64 -dw -Wf\"-A dbl4\" -sx6 -ftrace -C vopt -Wf"-init stack=nan" -Wl"-f nan" -Wf"-P nh" -Wf,-pvctl noassume loopcnt=10000 -L transform -I $(MODDIR) -I $(MODDIR)/oce -I $(NCDF_INC)' 
    261261echo '#-Q- sx6nec  F_F = $(F_O)' 
    262262echo '#-Q- sx6nec  L_X = $(L_O) -ftrace' 
    263263echo '#-Q- sx8brodie  # Compiler options NEMO (CEA SX6-NEC) ' 
    264 echo '#-Q- sx8brodie  F_O = -dw -Wf\"-A idbl4\" -sx8 -C vopt -Wf"-init stack=nan" -Wl"-f nan" -Wf"-P nh" -Wf,-pvctl noassume loopcnt=10000 -L transform -I $(MODDIR) -I $(MODDIR)/oce' 
     264echo '#-Q- sx8brodie  F_O = -dw -Wf\"-A idbl4\" -sx8 -C vopt -Wf"-init stack=nan" -Wl"-f nan" -Wf"-P nh" -Wf,-pvctl noassume loopcnt=10000 -L transform -I $(MODDIR) -I $(MODDIR)/oce -I $(NCDF_INC)' 
    265265echo '#-Q- sx8brodie  F_F = $(F_O)' 
    266266echo '#-Q- sx8brodie  L_X = $(L_O)' 
    267267echo '#-Q- sxdkrz  # Compiler options for NEMO (DKRZ SX6-NEC) ' 
    268 echo '#-Q- sxdkrz  F_O = -ew -sx6 -ftrace -C vopt -Wf"-init stack=nan" -Wl"-f nan" -Wf"-P nh" -Wf"-pvctl noassume loopcnt=10000" -L transform -I $(MODDIR) -I $(MODDIR)/oce' 
     268echo '#-Q- sxdkrz  F_O = -ew -sx6 -ftrace -C vopt -Wf"-init stack=nan" -Wl"-f nan" -Wf"-P nh" -Wf"-pvctl noassume loopcnt=10000" -L transform -I $(MODDIR) -I $(MODDIR)/oce -I $(NCDF_INC)' 
    269269echo '#-Q- sxdkrz  F_F = $(F_O)' 
    270270echo '#-Q- sxdkrz  L_X = $(L_O) -ftrace' 
    271271echo '#-Q- eshpux  # Compiler options for NEMO (Earth Simulator)' 
    272272echo '#-Q- eshpux  # for super perfs!' 
    273 echo '#-Q- eshpux  # F_O = $(FTRACE) -pi nest=5 line=10000 expin=Fmpplib.F -Wf,-A idbl4 -C hopt -Wf"-P nh" -Wf,-pvctl noassume loopcnt=10000 -L transform -I $(MODDIR) -I $(MODDIR)/oce' 
     273echo '#-Q- eshpux  # F_O = $(FTRACE) -pi nest=5 line=10000 expin=Fmpplib.F -Wf,-A idbl4 -C hopt -Wf"-P nh" -Wf,-pvctl noassume loopcnt=10000 -L transform -I $(MODDIR) -I $(MODDIR)/oce -I $(NCDF_INC)' 
    274274echo '#-Q- eshpux  # regular options!' 
    275 echo '#-Q- eshpux  F_O = $(FTRACE) -Wf,-A idbl4 -C vopt -P stack -Wf"-P nh" -Wf,-pvctl noassume loopcnt=10000 -L transform -Wf,-pvctl nomsg -Wf"-O nomsg" -I $(MODDIR) -I $(MODDIR)/oce' 
     275echo '#-Q- eshpux  F_O = $(FTRACE) -Wf,-A idbl4 -C vopt -P stack -Wf"-P nh" -Wf,-pvctl noassume loopcnt=10000 -L transform -Wf,-pvctl nomsg -Wf"-O nomsg" -I $(MODDIR) -I $(MODDIR)/oce -I $(NCDF_INC)' 
    276276echo '#-Q- eshpux  F_F = $(F_O)' 
    277277echo '#-Q- eshpux  L_X = $(L_O)' 
    278278echo '#-Q- linux  # Compiler options for NEMO (pgf version)' 
    279 echo '#-Q- linux  F_O = -Mlist -O3 -byteswapio -r8  -I $(MODDIR) -I$(MODDIR)/oce' 
     279echo '#-Q- linux  F_O = -Mlist -O3 -byteswapio -r8  -I $(MODDIR) -I$(MODDIR)/oce -I $(NCDF_INC)' 
    280280echo '#-Q- linux  F_F = $(F_O)' 
    281281echo '#-Q- linux  L_X = -r8 -O3' 
    282282echo '#-Q- lxiv7  # Compiler options for NEMO (ifc version)' 
    283 echo '#-Q- lxiv7  F_O = -O3 -r8  -I $(MODDIR) -I$(MODDIR)/oce' 
     283echo '#-Q- lxiv7  F_O = -O3 -r8  -I $(MODDIR) -I$(MODDIR)/oce -I $(NCDF_INC)' 
    284284echo '#-Q- lxiv7  L_X = -r8 -O3' 
    285285echo '#-Q- lxiv8  # Compiler options for NEMO (ifort version)' 
     
    288288echo '#-Q- lxiv8  L_X = -r8 -O3' 
    289289echo '#-Q- g95  # Compiler options for NEMO (g95 version)' 
    290 echo '#-Q- g95  F_O = -O3 -fno-second-underscore -r8 -funroll-all-loops -I $(MODDIR) -I $(MODDIR)/oce' 
     290echo '#-Q- g95  F_O = -O3 -fno-second-underscore -r8 -funroll-all-loops -I $(MODDIR) -I $(MODDIR)/oce -I $(NCDF_INC)' 
    291291echo '#-Q- g95  F_F = $(F_O)' 
    292292echo '#-Q- g95  L_X = -r8 -O3' 
    293293echo '#-Q- aix    # Compiler options for NEMO (aix version)' 
    294 echo '#-Q- aix    F_O = -O3 -qsave -qrealsize=8 -qsuffix=f=f90 -qsuffix=cpp=F90 -qextname -qsource -q64 -qlargepage -qmaxmem=-1 -I $(MODDIR) -I $(MODDIR)/oce'  
    295 echo '#-Q- aix    F_F = -O3 -qsave -qrealsize=8 -qsuffix=f=f -qsuffix=cpp=F -qfixed -qextname -qsource -q64 -qlargepage -qmaxmem=-1 -I $(MODDIR) -I $(MODDIR)/oce'  
     294echo '#-Q- aix    F_O = -O3 -qsave -qrealsize=8 -qsuffix=f=f90 -qsuffix=cpp=F90 -qextname -qsource -q64 -qlargepage -qmaxmem=-1 -I $(MODDIR) -I $(MODDIR)/oce -I $(NCDF_INC)'  
     295echo '#-Q- aix    F_F = -O3 -qsave -qrealsize=8 -qsuffix=f=f -qsuffix=cpp=F -qfixed -qextname -qsource -q64 -qlargepage -qmaxmem=-1 -I $(MODDIR) -I $(MODDIR)/oce -I $(NCDF_INC)'  
    296296echo '#-Q- aix   L_O = $(F_P) -q64 -O3' 
    297297echo '#-Q- aix   L_X = $(L_O)' 
    298298echo '#-Q- osxxlf    # Compiler options for NEMO (osxxlf version)' 
    299 echo '#-Q- osxxlf    F_O = -O3 -qsave -qrealsize=8 -qsuffix=f=f90 -qsuffix=cpp=F90 -qsource -qmaxmem=-1 -I $(MODDIR) -I $(MODDIR)/oce'  
    300 echo '#-Q- osxxlf    F_F = -O3 -qsave -qrealsize=8 -qsuffix=f=f -qsuffix=cpp=F -qfixed -qsource -qmaxmem=-1 -I $(MODDIR) -I $(MODDIR)/oce'  
     299echo '#-Q- osxxlf    F_O = -O3 -qsave -qrealsize=8 -qsuffix=f=f90 -qsuffix=cpp=F90 -qsource -qmaxmem=-1 -I $(MODDIR) -I $(MODDIR)/oce -I $(NCDF_INC)'  
     300echo '#-Q- osxxlf    F_F = -O3 -qsave -qrealsize=8 -qsuffix=f=f -qsuffix=cpp=F -qfixed -qsource -qmaxmem=-1 -I $(MODDIR) -I $(MODDIR)/oce -I $(NCDF_INC)'  
    301301echo '#-Q- osxxlf    L_X = -qrealsize=8 -O3' 
    302302 
     
    469469                if [ $fuse0 != "Agrif_Types" ]  
    470470                then 
     471                if [ $fuse0 != "netcdf" ]  
     472                then 
    471473          lfuse0=$fuse0.f90 
    472474          [ -f $fuse0.F90 ] && lfuse0=$fuse0.F90 
    473475          luse0="$luse0\n$lfuse0\n\$(MODEL_LIB)($fuse0.o)" 
     476                fi 
    474477                fi 
    475478                fi 
     
    489492                    if [ $fuse0 != "Agrif_Types" ]  
    490493                    then 
     494                    if [ $fuse0 != "netcdf" ]  
     495                    then 
    491496              lfuse0=$fuse0.f90 
    492497              [ -f $fuse0.F90 ] && lfuse0=$fuse0.F90 
    493498              luse0="$luse0\n$lfuse0\n\$(MODEL_LIB)($fuse0.o)" 
     499                    fi 
    494500                    fi 
    495501                    fi 
     
    507513        then 
    508514        if [ $fuse1 != "Agrif_Types" ]  
     515        then 
     516        if [ $fuse1 != "netcdf" ]  
    509517        then 
    510518       lfuse1=$fuse1.f90 
     
    518526                then 
    519527                if [ $fuse2 != "Agrif_Types" ]  
     528                then 
     529                if [ $fuse2 != "netcdf" ]  
    520530                then 
    521531          lfuse2=$fuse2.f90 
     
    531541                    if [ $fuse3 != "Agrif_Types" ]  
    532542                    then 
     543                    if [ $fuse3 != "netcdf" ]  
     544                    then 
    533545         luse3="$luse3\n$lfuse3\n\$(MODEL_LIB)($fuse3.o)" 
     546                    fi          
    534547                    fi          
    535548                    fi          
     
    539552                fi 
    540553                fi 
     554                fi 
    541555      done 
     556        fi 
    542557        fi 
    543558        fi 
     
    641656echo '       ln -sf ../OPA_SRC/DTA/*.[Ffh]90      . ; \' 
    642657echo '       ln -sf ../OPA_SRC/SBC/*.[Ffh]90      . ; \' 
     658echo '       ln -sf ../OPA_SRC/IOM/*.[Ffh]90      . ; \' 
    643659echo '  fi ' 
    644660echo '   @check=`grep LIM_SRC .config`              ; \' 
Note: See TracChangeset for help on using the changeset viewer.