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 9169 for branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC – NEMO

Ignore:
Timestamp:
2017-12-26T17:32:56+01:00 (6 years ago)
Author:
gm
Message:

dev_merge_2017: all SRC: finalize the removal of useless warning when reading namelist_cfg + remove all nn_closea + nn_msh replaced by a logical

Location:
branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC
Files:
29 edited

Legend:

Unmodified
Added
Removed
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/BDY/bdyini.F90

    r9168 r9169  
    421421            ! keep full control of the configuration namelist 
    422422            READ  ( numnam_cfg, nambdy_index, IOSTAT = ios, ERR = 904 ) 
    423 904         IF( ios /= 0 ) CALL ctl_nam ( ios , 'nambdy_index in configuration namelist', lwp ) 
     423904         IF( ios /= 0 )   CALL ctl_nam ( ios , 'nambdy_index in configuration namelist', lwp ) 
    424424            IF(lwm) WRITE ( numond, nambdy_index ) 
    425425 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/C1D/domc1d.F90

    r9168 r9169  
    5959      REAL(wp) , DIMENSION(jpidta,jpjdta) ::  gphidta, glamdta, zdist ! Global lat/lon 
    6060      !! 
    61       NAMELIST/namdom/ nn_bathy, rn_bathy , rn_e3zps_min, rn_e3zps_rat, nn_msh, rn_hmin,   & 
    62          &             rn_atfp     , rn_rdt      ,nn_closea , ln_crs,  jphgr_msh, & 
     61      NAMELIST/namdom/ nn_bathy, rn_bathy , rn_e3zps_min, rn_e3zps_rat, ln_meshmask, rn_hmin,   & 
     62         &             rn_atfp     , rn_rdt , ln_crs,  jphgr_msh, & 
    6363         &             ppglam0, ppgphi0, ppe1_deg, ppe2_deg, ppe1_m, ppe2_m, & 
    6464         &             ppsur, ppa0, ppa1, ppkth, ppacr, ppdzmin, pphmax, ldbletanh, & 
     
    6969      READ  ( numnam_ref, namdom, IOSTAT = ios, ERR = 901 ) 
    7070901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namdom in reference namelist', lwp ) 
    71       ! 
    7271      REWIND( numnam_cfg )              ! Namelist namdom in configuration namelist : space & time domain (bathymetry, mesh, timestep) 
    7372      READ  ( numnam_cfg, namdom, IOSTAT = ios, ERR = 902 ) 
     
    182181      jpjzoom = iloc(2) + njmpp - 2  ! corner index of the zoom domain. 
    183182 
    184       IF (lwp) THEN 
     183      IF(lwp) THEN 
    185184         WRITE(numout,*) 
    186185         WRITE(numout,*) 'dom_c1d : compute jpizoom & jpjzoom from global mesh and given coordinates' 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/CRS/crs.F90

    r9019 r9169  
    122122                                                !: 1 = binning centers at equator (north fold my have artifacts)      
    123123                                                !:    for even reduction factors, equator placed in bin biased south 
    124       INTEGER           :: nn_msh_crs = 1       !: Organization of mesh mask output 
    125                                                 !: 0 = no mesh mask output 
    126                                                 !: 1 = unified mesh mask output 
    127                                                 !: 2 = 2 separate mesh mask output 
    128                                                 !: 3 = 3 separate mesh mask output 
    129       INTEGER           :: nn_crs_kz    =    0       !: type of Kz coarsening ( =0->VOL ; =1->MAX ; =2->MIN)  
    130       LOGICAL           :: ln_crs_wn    = .FALSE.    !: coarsening wn or computation using horizontal divergence  
     124      LOGICAL           :: ln_msh_crs = 1          !: =T Create a meshmask file for CRS 
     125      INTEGER           :: nn_crs_kz    =    0     !: type of Kz coarsening ( =0->VOL ; =1->MAX ; =2->MIN)  
     126      LOGICAL           :: ln_crs_wn    = .FALSE.  !: coarsening wn or computation using horizontal divergence  
    131127      ! 
    132128      INTEGER           :: nrestx, nresty       !: for determining odd or even reduction factor 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/CRS/crsdomwri.F90

    r9125 r9169  
    4848      !! ** Output files :   mesh_hgr_crs.nc, mesh_zgr_crs.nc, mesh_mask.nc 
    4949      !!---------------------------------------------------------------------- 
    50       !! 
    51       INTEGER           ::   inum0    ! temprary units for 'mesh_mask.nc' file 
    52       INTEGER           ::   inum1    ! temprary units for 'mesh.nc'      file 
    53       INTEGER           ::   inum2    ! temprary units for 'mask.nc'      file 
    54       INTEGER           ::   inum3    ! temprary units for 'mesh_hgr.nc'  file 
    55       INTEGER           ::   inum4    ! temprary units for 'mesh_zgr.nc'  file 
     50      INTEGER           ::   ji, jj, jk   ! dummy loop indices 
     51      INTEGER           ::   inum         ! local units for 'mesh_mask.nc' file 
    5652      INTEGER           ::   iif, iil, ijf, ijl 
    57       CHARACTER(len=21) ::   clnam0   ! filename (mesh and mask informations) 
    58       CHARACTER(len=21) ::   clnam1   ! filename (mesh informations) 
    59       CHARACTER(len=21) ::   clnam2   ! filename (mask informations) 
    60       CHARACTER(len=21) ::   clnam3   ! filename (horizontal mesh informations) 
    61       CHARACTER(len=21) ::   clnam4   ! filename (vertical   mesh informations) 
    62       INTEGER           ::   ji, jj, jk   ! dummy loop indices 
    63       !                                   !  workspaces 
    64       REAL(wp), DIMENSION(jpi_crs,jpj_crs    ) :: zprt, zprw  
    65       REAL(wp), DIMENSION(jpi_crs,jpj_crs,jpk) :: zdepu, zdepv 
    66       REAL(wp), DIMENSION(jpi_crs,jpj_crs    ) :: ze3tp, ze3wp 
    67       !!---------------------------------------------------------------------- 
    68       ! 
    69       ze3tp(:,:) = 0.0 
    70       ze3wp(:,:) = 0.0 
    71  
     53      CHARACTER(len=21) ::   clnam        ! filename (mesh and mask informations) 
     54      !                                   !  workspace 
     55      REAL(wp), DIMENSION(jpi_crs,jpj_crs    ) ::   zprt, zprw  
     56      REAL(wp), DIMENSION(jpi_crs,jpj_crs,jpk) ::   zdepu, zdepv 
     57      !!---------------------------------------------------------------------- 
     58      ! 
    7259      ! 
    7360      IF(lwp) WRITE(numout,*) 
    74       IF(lwp) WRITE(numout,*) 'crs_dom_wri : create NetCDF mesh and mask information file(s)' 
    75       IF(lwp) WRITE(numout,*) '~~~~~~~' 
    76        
    77       clnam0 = 'mesh_mask_crs'  ! filename (mesh and mask informations) 
    78       clnam1 = 'mesh_crs'       ! filename (mesh informations) 
    79       clnam2 = 'mask_crs'       ! filename (mask informations) 
    80       clnam3 = 'mesh_hgr_crs'   ! filename (horizontal mesh informations) 
    81       clnam4 = 'mesh_zgr_crs'   ! filename (vertical   mesh informations) 
    82        
    83  
    84       SELECT CASE ( MOD(nn_msh_crs, 3) ) 
    85          !                                  ! ============================ 
    86       CASE ( 1 )                            !  create 'mesh_mask.nc' file 
    87          !                                  ! ============================ 
    88          CALL iom_open( TRIM(clnam0), inum0, ldwrt = .TRUE., kiolib = jprstlib ) 
    89          inum2 = inum0                                            ! put all the informations 
    90          inum3 = inum0                                            ! in unit inum0 
    91          inum4 = inum0 
    92           
    93          !                                  ! ============================ 
    94       CASE ( 2 )                            !  create 'mesh.nc' and  
    95          !                                  !         'mask.nc' files 
    96          !                                  ! ============================ 
    97          CALL iom_open( TRIM(clnam1), inum1, ldwrt = .TRUE., kiolib = jprstlib ) 
    98          CALL iom_open( TRIM(clnam2), inum2, ldwrt = .TRUE., kiolib = jprstlib ) 
    99          inum3 = inum1                                            ! put mesh informations  
    100          inum4 = inum1                                            ! in unit inum1  
    101          !                                  ! ============================ 
    102       CASE ( 0 )                            !  create 'mesh_hgr.nc' 
    103          !                                  !         'mesh_zgr.nc' and 
    104          !                                  !         'mask.nc'     files 
    105          !                                  ! ============================ 
    106          CALL iom_open( TRIM(clnam2), inum2, ldwrt = .TRUE., kiolib = jprstlib ) 
    107          CALL iom_open( TRIM(clnam3), inum3, ldwrt = .TRUE., kiolib = jprstlib ) 
    108          CALL iom_open( TRIM(clnam4), inum4, ldwrt = .TRUE., kiolib = jprstlib ) 
    109          ! 
    110       END SELECT 
     61      IF(lwp) WRITE(numout,*) 'crs_dom_wri : create NetCDF mesh and mask file' 
     62      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~' 
     63       
     64      clnam = 'mesh_mask_crs'  ! filename (mesh and mask informations) 
     65       
     66 
     67      !                            ! ============================ 
     68      !                            !  create 'mesh_mask.nc' file 
     69      !                            ! ============================ 
     70      ! 
     71      CALL iom_open( TRIM(clnam), inum, ldwrt = .TRUE., kiolib = jprstlib ) 
    11172  
    112       !======================================================== 
    113       !                                                         ! masks (inum2)  
    114       CALL iom_rstput( 0, 0, inum2, 'tmask', tmask_crs, ktype = jp_i1 )     !    ! land-sea mask 
    115       CALL iom_rstput( 0, 0, inum2, 'umask', umask_crs, ktype = jp_i1 ) 
    116       CALL iom_rstput( 0, 0, inum2, 'vmask', vmask_crs, ktype = jp_i1 ) 
    117       CALL iom_rstput( 0, 0, inum2, 'fmask', fmask_crs, ktype = jp_i1 ) 
     73      CALL iom_rstput( 0, 0, inum, 'tmask', tmask_crs, ktype = jp_i1 )    ! land-sea mask 
     74      CALL iom_rstput( 0, 0, inum, 'umask', umask_crs, ktype = jp_i1 ) 
     75      CALL iom_rstput( 0, 0, inum, 'vmask', vmask_crs, ktype = jp_i1 ) 
     76      CALL iom_rstput( 0, 0, inum, 'fmask', fmask_crs, ktype = jp_i1 ) 
    11877       
    11978       
     
    147106      ENDIF 
    148107       
    149       CALL iom_rstput( 0, 0, inum2, 'tmaskutil', tmask_i_crs, ktype = jp_i1 ) 
     108      CALL iom_rstput( 0, 0, inum, 'tmaskutil', tmask_i_crs, ktype = jp_i1 ) 
    150109                                   !    ! unique point mask 
    151110      CALL dom_uniq_crs( zprw, 'U' ) 
    152111      zprt = umask_crs(:,:,1) * zprw 
    153       CALL iom_rstput( 0, 0, inum2, 'umaskutil', zprt, ktype = jp_i1 )   
     112      CALL iom_rstput( 0, 0, inum, 'umaskutil', zprt, ktype = jp_i1 )   
    154113      CALL dom_uniq_crs( zprw, 'V' ) 
    155114      zprt = vmask_crs(:,:,1) * zprw 
    156       CALL iom_rstput( 0, 0, inum2, 'vmaskutil', zprt, ktype = jp_i1 )   
     115      CALL iom_rstput( 0, 0, inum, 'vmaskutil', zprt, ktype = jp_i1 )   
    157116      CALL dom_uniq_crs( zprw, 'F' ) 
    158117      zprt = fmask_crs(:,:,1) * zprw 
    159       CALL iom_rstput( 0, 0, inum2, 'fmaskutil', zprt, ktype = jp_i1 )   
     118      CALL iom_rstput( 0, 0, inum, 'fmaskutil', zprt, ktype = jp_i1 )   
    160119      !======================================================== 
    161       !                                                         ! horizontal mesh (inum3) 
    162       CALL iom_rstput( 0, 0, inum3, 'glamt', glamt_crs, ktype = jp_r4 )     !    ! latitude 
    163       CALL iom_rstput( 0, 0, inum3, 'glamu', glamu_crs, ktype = jp_r4 ) 
    164       CALL iom_rstput( 0, 0, inum3, 'glamv', glamv_crs, ktype = jp_r4 ) 
    165       CALL iom_rstput( 0, 0, inum3, 'glamf', glamf_crs, ktype = jp_r4 ) 
    166        
    167       CALL iom_rstput( 0, 0, inum3, 'gphit', gphit_crs, ktype = jp_r4 )     !    ! longitude 
    168       CALL iom_rstput( 0, 0, inum3, 'gphiu', gphiu_crs, ktype = jp_r4 ) 
    169       CALL iom_rstput( 0, 0, inum3, 'gphiv', gphiv_crs, ktype = jp_r4 ) 
    170       CALL iom_rstput( 0, 0, inum3, 'gphif', gphif_crs, ktype = jp_r4 ) 
    171        
    172       CALL iom_rstput( 0, 0, inum3, 'e1t', e1t_crs, ktype = jp_r8 )         !    ! e1 scale factors 
    173       CALL iom_rstput( 0, 0, inum3, 'e1u', e1u_crs, ktype = jp_r8 ) 
    174       CALL iom_rstput( 0, 0, inum3, 'e1v', e1v_crs, ktype = jp_r8 ) 
    175       CALL iom_rstput( 0, 0, inum3, 'e1f', e1f_crs, ktype = jp_r8 ) 
    176        
    177       CALL iom_rstput( 0, 0, inum3, 'e2t', e2t_crs, ktype = jp_r8 )         !    ! e2 scale factors 
    178       CALL iom_rstput( 0, 0, inum3, 'e2u', e2u_crs, ktype = jp_r8 ) 
    179       CALL iom_rstput( 0, 0, inum3, 'e2v', e2v_crs, ktype = jp_r8 ) 
    180       CALL iom_rstput( 0, 0, inum3, 'e2f', e2f_crs, ktype = jp_r8 ) 
    181        
    182       CALL iom_rstput( 0, 0, inum3, 'ff', ff_crs, ktype = jp_r8 )           !    ! coriolis factor 
     120      !                                                         ! horizontal mesh 
     121      CALL iom_rstput( 0, 0, inum, 'glamt', glamt_crs, ktype = jp_r4 )     !    ! latitude 
     122      CALL iom_rstput( 0, 0, inum, 'glamu', glamu_crs, ktype = jp_r4 ) 
     123      CALL iom_rstput( 0, 0, inum, 'glamv', glamv_crs, ktype = jp_r4 ) 
     124      CALL iom_rstput( 0, 0, inum, 'glamf', glamf_crs, ktype = jp_r4 ) 
     125       
     126      CALL iom_rstput( 0, 0, inum, 'gphit', gphit_crs, ktype = jp_r4 )     !    ! longitude 
     127      CALL iom_rstput( 0, 0, inum, 'gphiu', gphiu_crs, ktype = jp_r4 ) 
     128      CALL iom_rstput( 0, 0, inum, 'gphiv', gphiv_crs, ktype = jp_r4 ) 
     129      CALL iom_rstput( 0, 0, inum, 'gphif', gphif_crs, ktype = jp_r4 ) 
     130       
     131      CALL iom_rstput( 0, 0, inum, 'e1t', e1t_crs, ktype = jp_r8 )         !    ! e1 scale factors 
     132      CALL iom_rstput( 0, 0, inum, 'e1u', e1u_crs, ktype = jp_r8 ) 
     133      CALL iom_rstput( 0, 0, inum, 'e1v', e1v_crs, ktype = jp_r8 ) 
     134      CALL iom_rstput( 0, 0, inum, 'e1f', e1f_crs, ktype = jp_r8 ) 
     135       
     136      CALL iom_rstput( 0, 0, inum, 'e2t', e2t_crs, ktype = jp_r8 )         !    ! e2 scale factors 
     137      CALL iom_rstput( 0, 0, inum, 'e2u', e2u_crs, ktype = jp_r8 ) 
     138      CALL iom_rstput( 0, 0, inum, 'e2v', e2v_crs, ktype = jp_r8 ) 
     139      CALL iom_rstput( 0, 0, inum, 'e2f', e2f_crs, ktype = jp_r8 ) 
     140       
     141      CALL iom_rstput( 0, 0, inum, 'ff', ff_crs, ktype = jp_r8 )           !    ! coriolis factor 
    183142 
    184143      !======================================================== 
    185       !                                                         ! vertical mesh (inum4)  
     144      !                                                         ! vertical mesh 
    186145!     ! note that mbkt is set to 1 over land ==> use surface tmask_crs 
    187146      zprt(:,:) = tmask_crs(:,:,1) * REAL( mbkt_crs(:,:) , wp ) 
    188       CALL iom_rstput( 0, 0, inum4, 'mbathy', zprt, ktype = jp_i2 )     !    ! nb of ocean T-points 
    189  
    190       IF( ln_zps ) THEN                       ! z-coordinate - partial steps 
    191  
    192              
    193          IF ( nn_msh_crs <= 6 ) THEN 
    194             CALL iom_rstput( 0, 0, inum4, 'e3t', e3t_crs )       
    195             CALL iom_rstput( 0, 0, inum4, 'e3w', e3w_crs )       
    196             CALL iom_rstput( 0, 0, inum4, 'e3u', e3u_crs )       
    197             CALL iom_rstput( 0, 0, inum4, 'e3v', e3v_crs )       
    198          ELSE 
    199             DO jj = 1,jpj_crs    
    200                DO ji = 1,jpi_crs 
    201                   ze3tp(ji,jj) = e3t_crs(ji,jj,mbkt_crs(ji,jj)) * tmask_crs(ji,jj,1) 
    202                   ze3wp(ji,jj) = e3w_crs(ji,jj,mbkt_crs(ji,jj)) * tmask_crs(ji,jj,1) 
    203                END DO 
    204             END DO 
    205  
    206             CALL crs_lbc_lnk( ze3tp,'T', 1.0 ) 
    207             CALL crs_lbc_lnk( ze3wp,'W', 1.0 ) 
    208    
    209             CALL iom_rstput( 0, 0, inum4, 'e3t_ps', ze3tp )       
    210             CALL iom_rstput( 0, 0, inum4, 'e3w_ps', ze3wp ) 
    211          ENDIF 
    212  
    213          IF ( nn_msh_crs <= 3 ) THEN 
    214             CALL iom_rstput( 0, 0, inum4, 'gdept', gdept_crs, ktype = jp_r4 )  
    215             DO jk = 1,jpk    
    216                DO jj = 1, jpj_crsm1    
    217                   DO ji = 1, jpi_crsm1  ! jes what to do for fs_jpim1??vector opt. 
    218                      zdepu(ji,jj,jk) = MIN( gdept_crs(ji,jj,jk) , gdept_crs(ji+1,jj  ,jk) ) * umask_crs(ji,jj,jk) 
    219                      zdepv(ji,jj,jk) = MIN( gdept_crs(ji,jj,jk) , gdept_crs(ji  ,jj+1,jk) ) * vmask_crs(ji,jj,jk) 
    220                   END DO    
    221                END DO    
    222             END DO 
    223  
    224             CALL crs_lbc_lnk( zdepu,'U', 1. )   ;   CALL crs_lbc_lnk( zdepv,'V', 1. )  
    225             CALL iom_rstput( 0, 0, inum4, 'gdepu', zdepu, ktype = jp_r4 ) 
    226             CALL iom_rstput( 0, 0, inum4, 'gdepv', zdepv, ktype = jp_r4 ) 
    227             CALL iom_rstput( 0, 0, inum4, 'gdepw', gdepw_crs, ktype = jp_r4 ) 
    228          ELSE 
    229             DO jj = 1,jpj_crs    
    230                DO ji = 1,jpi_crs 
    231                   zprt(ji,jj) = gdept_0(ji,jj,mbkt(ji,jj)  ) * tmask(ji,jj,1) 
    232                   zprw(ji,jj) = gdepw_0(ji,jj,mbkt(ji,jj)+1) * tmask(ji,jj,1) 
    233                END DO 
    234             END DO 
    235             CALL iom_rstput( 0, 0, inum4, 'hdept', zprt, ktype = jp_r4 )      
    236             CALL iom_rstput( 0, 0, inum4, 'hdepw', zprw, ktype = jp_r4 )  
    237          ENDIF 
    238  
    239          CALL iom_rstput( 0, 0, inum4, 'gdept_1d', gdept_1d )     !    ! reference z-coord. 
    240          CALL iom_rstput( 0, 0, inum4, 'gdepw_1d', gdepw_1d ) 
    241          CALL iom_rstput( 0, 0, inum4, 'e3t_1d'  , e3t_1d   ) 
    242          CALL iom_rstput( 0, 0, inum4, 'e3w_1d'  , e3w_1d   ) 
    243  
    244          CALL iom_rstput(  0, 0, inum4, 'ocean_volume_t', ocean_volume_crs_t )  
    245          CALL iom_rstput(  0, 0, inum4, 'facvol_t' , facvol_t  )  
    246          CALL iom_rstput(  0, 0, inum4, 'facvol_w' , facvol_w  )  
    247          CALL iom_rstput(  0, 0, inum4, 'facsurfu' , facsurfu  )  
    248          CALL iom_rstput(  0, 0, inum4, 'facsurfv' , facsurfv  )  
    249          CALL iom_rstput(  0, 0, inum4, 'e1e2w_msk', e1e2w_msk )  
    250          CALL iom_rstput(  0, 0, inum4, 'e2e3u_msk', e2e3u_msk )  
    251          CALL iom_rstput(  0, 0, inum4, 'e1e3v_msk', e1e3v_msk ) 
    252          CALL iom_rstput(  0, 0, inum4, 'e1e2w'    , e1e2w_crs )  
    253          CALL iom_rstput(  0, 0, inum4, 'e2e3u'    , e2e3u_crs )  
    254          CALL iom_rstput(  0, 0, inum4, 'e1e3v'    , e1e3v_crs ) 
    255          CALL iom_rstput(  0, 0, inum4, 'bt'       , bt_crs    ) 
    256          CALL iom_rstput(  0, 0, inum4, 'r1_bt'    , r1_bt_crs ) 
    257  
    258          CALL iom_rstput(  0, 0, inum4, 'crs_surfu_wgt', crs_surfu_wgt )  
    259          CALL iom_rstput(  0, 0, inum4, 'crs_surfv_wgt', crs_surfv_wgt )  
    260          CALL iom_rstput(  0, 0, inum4, 'crs_volt_wgt' , crs_volt_wgt  )  
    261  
    262       ENDIF 
    263        
    264      IF( ln_zco ) THEN 
    265          !                                                      ! z-coordinate - full steps 
    266         CALL iom_rstput( 0, 0, inum4, 'gdept_1d', gdept_1d )     !    ! depth 
    267         CALL iom_rstput( 0, 0, inum4, 'gdepw_1d', gdepw_1d ) 
    268         CALL iom_rstput( 0, 0, inum4, 'e3t_1d'  , e3t_1d   )     !    ! scale factors 
    269         CALL iom_rstput( 0, 0, inum4, 'e3w_1d'  , e3w_1d   ) 
    270      ENDIF 
     147      CALL iom_rstput( 0, 0, inum, 'mbathy', zprt, ktype = jp_i2 )     !    ! nb of ocean T-points 
     148      ! 
     149      CALL iom_rstput( 0, 0, inum, 'e3t', e3t_crs )       
     150      CALL iom_rstput( 0, 0, inum, 'e3w', e3w_crs )       
     151      CALL iom_rstput( 0, 0, inum, 'e3u', e3u_crs )       
     152      CALL iom_rstput( 0, 0, inum, 'e3v', e3v_crs )       
     153      ! 
     154      CALL iom_rstput( 0, 0, inum, 'gdept', gdept_crs, ktype = jp_r4 )  
     155      DO jk = 1,jpk    
     156         DO jj = 1, jpj_crsm1    
     157            DO ji = 1, jpi_crsm1  ! jes what to do for fs_jpim1??vector opt. 
     158               zdepu(ji,jj,jk) = MIN( gdept_crs(ji,jj,jk) , gdept_crs(ji+1,jj  ,jk) ) * umask_crs(ji,jj,jk) 
     159               zdepv(ji,jj,jk) = MIN( gdept_crs(ji,jj,jk) , gdept_crs(ji  ,jj+1,jk) ) * vmask_crs(ji,jj,jk) 
     160            END DO    
     161         END DO    
     162      END DO 
     163      CALL crs_lbc_lnk( zdepu,'U', 1. )   ;   CALL crs_lbc_lnk( zdepv,'V', 1. )  
     164      ! 
     165      CALL iom_rstput( 0, 0, inum, 'gdepu', zdepu, ktype = jp_r4 ) 
     166      CALL iom_rstput( 0, 0, inum, 'gdepv', zdepv, ktype = jp_r4 ) 
     167      CALL iom_rstput( 0, 0, inum, 'gdepw', gdepw_crs, ktype = jp_r4 ) 
     168      ! 
     169      CALL iom_rstput( 0, 0, inum, 'gdept_1d', gdept_1d )     !    ! reference z-coord. 
     170      CALL iom_rstput( 0, 0, inum, 'gdepw_1d', gdepw_1d ) 
     171      CALL iom_rstput( 0, 0, inum, 'e3t_1d'  , e3t_1d   ) 
     172      CALL iom_rstput( 0, 0, inum, 'e3w_1d'  , e3w_1d   ) 
     173      ! 
     174      CALL iom_rstput(  0, 0, inum, 'ocean_volume_t', ocean_volume_crs_t )  
     175      CALL iom_rstput(  0, 0, inum, 'facvol_t' , facvol_t  )  
     176      CALL iom_rstput(  0, 0, inum, 'facvol_w' , facvol_w  )  
     177      CALL iom_rstput(  0, 0, inum, 'facsurfu' , facsurfu  )  
     178      CALL iom_rstput(  0, 0, inum, 'facsurfv' , facsurfv  )  
     179      CALL iom_rstput(  0, 0, inum, 'e1e2w_msk', e1e2w_msk )  
     180      CALL iom_rstput(  0, 0, inum, 'e2e3u_msk', e2e3u_msk )  
     181      CALL iom_rstput(  0, 0, inum, 'e1e3v_msk', e1e3v_msk ) 
     182      CALL iom_rstput(  0, 0, inum, 'e1e2w'    , e1e2w_crs )  
     183      CALL iom_rstput(  0, 0, inum, 'e2e3u'    , e2e3u_crs )  
     184      CALL iom_rstput(  0, 0, inum, 'e1e3v'    , e1e3v_crs ) 
     185      CALL iom_rstput(  0, 0, inum, 'bt'       , bt_crs    ) 
     186      CALL iom_rstput(  0, 0, inum, 'r1_bt'    , r1_bt_crs ) 
     187      ! 
     188      CALL iom_rstput(  0, 0, inum, 'crs_surfu_wgt', crs_surfu_wgt )  
     189      CALL iom_rstput(  0, 0, inum, 'crs_surfv_wgt', crs_surfv_wgt )  
     190      CALL iom_rstput(  0, 0, inum, 'crs_volt_wgt' , crs_volt_wgt  )  
    271191      !                                     ! ============================ 
    272192      !                                     !        close the files  
    273193      !                                     ! ============================ 
    274       SELECT CASE ( MOD(nn_msh_crs, 3) ) 
    275       CASE ( 1 )                 
    276          CALL iom_close( inum0 ) 
    277       CASE ( 2 ) 
    278          CALL iom_close( inum1 ) 
    279          CALL iom_close( inum2 ) 
    280       CASE ( 0 ) 
    281          CALL iom_close( inum2 ) 
    282          CALL iom_close( inum3 ) 
    283          CALL iom_close( inum4 ) 
    284       END SELECT 
     194      CALL iom_close( inum ) 
    285195      ! 
    286196   END SUBROUTINE crs_dom_wri 
     
    296206      !!                2) check which elements have been changed 
    297207      !!---------------------------------------------------------------------- 
    298       ! 
    299208      CHARACTER(len=1)        , INTENT(in   ) ::   cdgrd   !  
    300209      REAL(wp), DIMENSION(:,:), INTENT(inout) ::   puniq   !  
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/CRS/crsini.F90

    r9168 r9169  
    7373      REAL(wp), DIMENSION(jpi,jpj,jpk) :: ze3t, ze3u, ze3v, ze3w 
    7474 
    75       NAMELIST/namcrs/ nn_factx, nn_facty, nn_binref, nn_msh_crs, nn_crs_kz, ln_crs_wn 
     75      NAMELIST/namcrs/ nn_factx, nn_facty, nn_binref, ln_msh_crs, nn_crs_kz, ln_crs_wn 
    7676      !!---------------------------------------------------------------------- 
    7777      ! 
     
    9696        WRITE(numout,*) '      coarsening factor in j-direction      nn_facty   = ', nn_facty 
    9797        WRITE(numout,*) '      bin centering preference              nn_binref  = ', nn_binref 
    98         WRITE(numout,*) '      create (=1) a mesh file or not (=0)   nn_msh_crs = ', nn_msh_crs 
     98        WRITE(numout,*) '      create a mesh file (=T)               ln_msh_crs = ', ln_msh_crs 
    9999        WRITE(numout,*) '      type of Kz coarsening (0,1,2)         nn_crs_kz  = ', nn_crs_kz 
    100100        WRITE(numout,*) '      wn coarsened or computed using hdivn  ln_crs_wn  = ', ln_crs_wn 
     
    228228     !--------------------------------------------------------- 
    229229 
    230      IF( nn_msh_crs > 0 ) THEN  
     230     IF( ln_msh_crs ) THEN  
    231231        CALL dom_grid_crs   ! Save the parent grid information  & Switch to coarse grid domain 
    232232        CALL crs_dom_wri      
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/DIA/diahsb.F90

    r9168 r9169  
    231231 
    232232   SUBROUTINE dia_hsb_rst( kt, cdrw ) 
    233      !!--------------------------------------------------------------------- 
    234      !!                   ***  ROUTINE dia_hsb_rst  *** 
    235      !!                      
    236      !! ** Purpose :   Read or write DIA file in restart file 
    237      !! 
    238      !! ** Method  :   use of IOM library 
    239      !!---------------------------------------------------------------------- 
    240      INTEGER         , INTENT(in) ::   kt     ! ocean time-step 
    241      CHARACTER(len=*), INTENT(in) ::   cdrw   ! "READ"/"WRITE" flag 
    242      ! 
    243      INTEGER ::   ji, jj, jk   ! dummy loop indices 
    244      !!---------------------------------------------------------------------- 
    245      ! 
    246      IF( TRIM(cdrw) == 'READ' ) THEN        ! Read/initialise  
    247         IF( ln_rstart ) THEN                   !* Read the restart file 
    248            ! 
    249            IF(lwp) WRITE(numout,*) '~~~~~~~' 
    250            IF(lwp) WRITE(numout,*) ' dia_hsb_rst at it= ', kt,' date= ', ndastp 
    251            IF(lwp) WRITE(numout,*) '~~~~~~~' 
    252            CALL iom_get( numror, 'frc_v', frc_v ) 
    253            CALL iom_get( numror, 'frc_t', frc_t ) 
    254            CALL iom_get( numror, 'frc_s', frc_s ) 
    255            IF( ln_linssh ) THEN 
    256               CALL iom_get( numror, 'frc_wn_t', frc_wn_t ) 
    257               CALL iom_get( numror, 'frc_wn_s', frc_wn_s ) 
    258            ENDIF 
    259            CALL iom_get( numror, jpdom_autoglo, 'surf_ini', surf_ini ) ! ice sheet coupling 
    260            CALL iom_get( numror, jpdom_autoglo, 'ssh_ini', ssh_ini(:,:) ) 
    261            CALL iom_get( numror, jpdom_autoglo, 'e3t_ini', e3t_ini(:,:,:) ) 
    262            CALL iom_get( numror, jpdom_autoglo, 'hc_loc_ini', hc_loc_ini(:,:,:) ) 
    263            CALL iom_get( numror, jpdom_autoglo, 'sc_loc_ini', sc_loc_ini(:,:,:) ) 
    264            IF( ln_linssh ) THEN 
    265               CALL iom_get( numror, jpdom_autoglo, 'ssh_hc_loc_ini', ssh_hc_loc_ini(:,:) ) 
    266               CALL iom_get( numror, jpdom_autoglo, 'ssh_sc_loc_ini', ssh_sc_loc_ini(:,:) ) 
    267            ENDIF 
    268        ELSE 
    269           IF(lwp) WRITE(numout,*) '~~~~~~~' 
    270           IF(lwp) WRITE(numout,*) ' dia_hsb at initial state ' 
    271           IF(lwp) WRITE(numout,*) '~~~~~~~' 
    272           surf_ini(:,:) = e1e2t(:,:) * tmask_i(:,:)         ! initial ocean surface 
    273           ssh_ini(:,:) = sshn(:,:)                          ! initial ssh 
    274           DO jk = 1, jpk 
    275              ! if ice sheet/oceqn coupling, need to mask ini variables here (mask could change at the next NEMO instance). 
    276              e3t_ini   (:,:,jk) = e3t_n(:,:,jk)                      * tmask(:,:,jk)  ! initial vertical scale factors 
    277              hc_loc_ini(:,:,jk) = tsn(:,:,jk,jp_tem) * e3t_n(:,:,jk) * tmask(:,:,jk)  ! initial heat content 
    278              sc_loc_ini(:,:,jk) = tsn(:,:,jk,jp_sal) * e3t_n(:,:,jk) * tmask(:,:,jk)  ! initial salt content 
    279           END DO 
    280           frc_v = 0._wp                                           ! volume       trend due to forcing 
    281           frc_t = 0._wp                                           ! heat content   -    -   -    -    
    282           frc_s = 0._wp                                           ! salt content   -    -   -    -         
    283           IF( ln_linssh ) THEN 
    284              IF ( ln_isfcav ) THEN 
    285                 DO ji=1,jpi 
    286                    DO jj=1,jpj 
    287                       ssh_hc_loc_ini(ji,jj) = tsn(ji,jj,mikt(ji,jj),jp_tem) * sshn(ji,jj)   ! initial heat content in ssh 
    288                       ssh_sc_loc_ini(ji,jj) = tsn(ji,jj,mikt(ji,jj),jp_sal) * sshn(ji,jj)   ! initial salt content in ssh 
    289                    ENDDO 
    290                 ENDDO 
    291              ELSE 
    292                 ssh_hc_loc_ini(:,:) = tsn(:,:,1,jp_tem) * sshn(:,:)   ! initial heat content in ssh 
    293                 ssh_sc_loc_ini(:,:) = tsn(:,:,1,jp_sal) * sshn(:,:)   ! initial salt content in ssh 
    294              END IF 
    295              frc_wn_t = 0._wp                                       ! initial heat content misfit due to free surface 
    296              frc_wn_s = 0._wp                                       ! initial salt content misfit due to free surface 
    297           ENDIF 
    298        ENDIF 
    299  
    300      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN   ! Create restart file 
    301         !                                   ! ------------------- 
    302         IF(lwp) WRITE(numout,*) '~~~~~~~' 
    303         IF(lwp) WRITE(numout,*) ' dia_hsb_rst at it= ', kt,' date= ', ndastp 
    304         IF(lwp) WRITE(numout,*) '~~~~~~~' 
    305  
    306         CALL iom_rstput( kt, nitrst, numrow, 'frc_v'   , frc_v     ) 
    307         CALL iom_rstput( kt, nitrst, numrow, 'frc_t'   , frc_t     ) 
    308         CALL iom_rstput( kt, nitrst, numrow, 'frc_s'   , frc_s     ) 
    309         IF( ln_linssh ) THEN 
    310            CALL iom_rstput( kt, nitrst, numrow, 'frc_wn_t', frc_wn_t ) 
    311            CALL iom_rstput( kt, nitrst, numrow, 'frc_wn_s', frc_wn_s ) 
    312         ENDIF 
    313         CALL iom_rstput( kt, nitrst, numrow, 'surf_ini', surf_ini )      ! ice sheet coupling 
    314         CALL iom_rstput( kt, nitrst, numrow, 'ssh_ini', ssh_ini(:,:) ) 
    315         CALL iom_rstput( kt, nitrst, numrow, 'e3t_ini', e3t_ini(:,:,:) ) 
    316         CALL iom_rstput( kt, nitrst, numrow, 'hc_loc_ini', hc_loc_ini(:,:,:) ) 
    317         CALL iom_rstput( kt, nitrst, numrow, 'sc_loc_ini', sc_loc_ini(:,:,:) ) 
    318         IF( ln_linssh ) THEN 
    319            CALL iom_rstput( kt, nitrst, numrow, 'ssh_hc_loc_ini', ssh_hc_loc_ini(:,:) ) 
    320            CALL iom_rstput( kt, nitrst, numrow, 'ssh_sc_loc_ini', ssh_sc_loc_ini(:,:) ) 
    321         ENDIF 
    322         ! 
    323      ENDIF 
    324      ! 
     233      !!--------------------------------------------------------------------- 
     234      !!                   ***  ROUTINE dia_hsb_rst  *** 
     235      !!                      
     236      !! ** Purpose :   Read or write DIA file in restart file 
     237      !! 
     238      !! ** Method  :   use of IOM library 
     239      !!---------------------------------------------------------------------- 
     240      INTEGER         , INTENT(in) ::   kt     ! ocean time-step 
     241      CHARACTER(len=*), INTENT(in) ::   cdrw   ! "READ"/"WRITE" flag 
     242      ! 
     243      INTEGER ::   ji, jj, jk   ! dummy loop indices 
     244      !!---------------------------------------------------------------------- 
     245      ! 
     246      IF( TRIM(cdrw) == 'READ' ) THEN        ! Read/initialise  
     247         IF( ln_rstart ) THEN                   !* Read the restart file 
     248            ! 
     249            IF(lwp) WRITE(numout,*) 
     250            IF(lwp) WRITE(numout,*) '   dia_hsb_rst : read hsb restart at it= ', kt,' date= ', ndastp 
     251            IF(lwp) WRITE(numout,*) 
     252            CALL iom_get( numror, 'frc_v', frc_v ) 
     253            CALL iom_get( numror, 'frc_t', frc_t ) 
     254            CALL iom_get( numror, 'frc_s', frc_s ) 
     255            IF( ln_linssh ) THEN 
     256               CALL iom_get( numror, 'frc_wn_t', frc_wn_t ) 
     257               CALL iom_get( numror, 'frc_wn_s', frc_wn_s ) 
     258            ENDIF 
     259            CALL iom_get( numror, jpdom_autoglo, 'surf_ini', surf_ini ) ! ice sheet coupling 
     260            CALL iom_get( numror, jpdom_autoglo, 'ssh_ini', ssh_ini(:,:) ) 
     261            CALL iom_get( numror, jpdom_autoglo, 'e3t_ini', e3t_ini(:,:,:) ) 
     262            CALL iom_get( numror, jpdom_autoglo, 'hc_loc_ini', hc_loc_ini(:,:,:) ) 
     263            CALL iom_get( numror, jpdom_autoglo, 'sc_loc_ini', sc_loc_ini(:,:,:) ) 
     264            IF( ln_linssh ) THEN 
     265               CALL iom_get( numror, jpdom_autoglo, 'ssh_hc_loc_ini', ssh_hc_loc_ini(:,:) ) 
     266               CALL iom_get( numror, jpdom_autoglo, 'ssh_sc_loc_ini', ssh_sc_loc_ini(:,:) ) 
     267            ENDIF 
     268          ELSE 
     269            IF(lwp) WRITE(numout,*) 
     270            IF(lwp) WRITE(numout,*) '   dia_hsb_rst : initialise hsb at initial state ' 
     271            IF(lwp) WRITE(numout,*) 
     272            surf_ini(:,:) = e1e2t(:,:) * tmask_i(:,:)         ! initial ocean surface 
     273            ssh_ini(:,:) = sshn(:,:)                          ! initial ssh 
     274            DO jk = 1, jpk 
     275              ! if ice sheet/oceqn coupling, need to mask ini variables here (mask could change at the next NEMO instance). 
     276               e3t_ini   (:,:,jk) = e3t_n(:,:,jk)                      * tmask(:,:,jk)  ! initial vertical scale factors 
     277               hc_loc_ini(:,:,jk) = tsn(:,:,jk,jp_tem) * e3t_n(:,:,jk) * tmask(:,:,jk)  ! initial heat content 
     278               sc_loc_ini(:,:,jk) = tsn(:,:,jk,jp_sal) * e3t_n(:,:,jk) * tmask(:,:,jk)  ! initial salt content 
     279            END DO 
     280            frc_v = 0._wp                                           ! volume       trend due to forcing 
     281            frc_t = 0._wp                                           ! heat content   -    -   -    -    
     282            frc_s = 0._wp                                           ! salt content   -    -   -    -         
     283            IF( ln_linssh ) THEN 
     284               IF( ln_isfcav ) THEN 
     285                  DO ji = 1, jpi 
     286                     DO jj = 1, jpj 
     287                        ssh_hc_loc_ini(ji,jj) = tsn(ji,jj,mikt(ji,jj),jp_tem) * sshn(ji,jj)   ! initial heat content in ssh 
     288                        ssh_sc_loc_ini(ji,jj) = tsn(ji,jj,mikt(ji,jj),jp_sal) * sshn(ji,jj)   ! initial salt content in ssh 
     289                     END DO 
     290                   END DO 
     291                ELSE 
     292                  ssh_hc_loc_ini(:,:) = tsn(:,:,1,jp_tem) * sshn(:,:)   ! initial heat content in ssh 
     293                  ssh_sc_loc_ini(:,:) = tsn(:,:,1,jp_sal) * sshn(:,:)   ! initial salt content in ssh 
     294               END IF 
     295               frc_wn_t = 0._wp                                       ! initial heat content misfit due to free surface 
     296               frc_wn_s = 0._wp                                       ! initial salt content misfit due to free surface 
     297            ENDIF 
     298         ENDIF 
     299         ! 
     300      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN   ! Create restart file 
     301         !                                   ! ------------------- 
     302         IF(lwp) WRITE(numout,*) 
     303         IF(lwp) WRITE(numout,*) '   dia_hsb_rst : write restart at it= ', kt,' date= ', ndastp 
     304         IF(lwp) WRITE(numout,*) 
     305         ! 
     306         CALL iom_rstput( kt, nitrst, numrow, 'frc_v'   , frc_v     ) 
     307         CALL iom_rstput( kt, nitrst, numrow, 'frc_t'   , frc_t     ) 
     308         CALL iom_rstput( kt, nitrst, numrow, 'frc_s'   , frc_s     ) 
     309         IF( ln_linssh ) THEN 
     310            CALL iom_rstput( kt, nitrst, numrow, 'frc_wn_t', frc_wn_t ) 
     311            CALL iom_rstput( kt, nitrst, numrow, 'frc_wn_s', frc_wn_s ) 
     312         ENDIF 
     313         CALL iom_rstput( kt, nitrst, numrow, 'surf_ini', surf_ini )      ! ice sheet coupling 
     314         CALL iom_rstput( kt, nitrst, numrow, 'ssh_ini', ssh_ini(:,:) ) 
     315         CALL iom_rstput( kt, nitrst, numrow, 'e3t_ini', e3t_ini(:,:,:) ) 
     316         CALL iom_rstput( kt, nitrst, numrow, 'hc_loc_ini', hc_loc_ini(:,:,:) ) 
     317         CALL iom_rstput( kt, nitrst, numrow, 'sc_loc_ini', sc_loc_ini(:,:,:) ) 
     318         IF( ln_linssh ) THEN 
     319            CALL iom_rstput( kt, nitrst, numrow, 'ssh_hc_loc_ini', ssh_hc_loc_ini(:,:) ) 
     320            CALL iom_rstput( kt, nitrst, numrow, 'ssh_sc_loc_ini', ssh_sc_loc_ini(:,:) ) 
     321         ENDIF 
     322         ! 
     323      ENDIF 
     324      ! 
    325325   END SUBROUTINE dia_hsb_rst 
    326326 
     
    338338      !!             - Compute coefficients for conversion 
    339339      !!--------------------------------------------------------------------------- 
    340       INTEGER ::   ierror   ! local integer 
    341       INTEGER ::   ios 
     340      INTEGER ::   ierror, ios   ! local integer 
    342341      !! 
    343342      NAMELIST/namhsb/ ln_diahsb 
    344343      !!---------------------------------------------------------------------- 
    345344      ! 
     345      IF(lwp) THEN 
     346         WRITE(numout,*) 
     347         WRITE(numout,*) 'dia_hsb_init : heat and salt budgets diagnostics' 
     348         WRITE(numout,*) '~~~~~~~~~~~~ ' 
     349      ENDIF 
    346350      REWIND( numnam_ref )              ! Namelist namhsb in reference namelist 
    347351      READ  ( numnam_ref, namhsb, IOSTAT = ios, ERR = 901) 
     
    350354      READ  ( numnam_cfg, namhsb, IOSTAT = ios, ERR = 902 ) 
    351355902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namhsb in configuration namelist', lwp ) 
    352       IF(lwm) WRITE ( numond, namhsb ) 
     356      IF(lwm) WRITE( numond, namhsb ) 
    353357 
    354358      IF(lwp) THEN 
    355          WRITE(numout,*) 
    356          WRITE(numout,*) 'dia_hsb_init : heat and salt budgets diagnostics' 
    357          WRITE(numout,*) '~~~~~~~~~~~~ ' 
    358359         WRITE(numout,*) '   Namelist  namhsb :' 
    359360         WRITE(numout,*) '      check the heat and salt budgets (T) or not (F)       ln_diahsb = ', ln_diahsb 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/DOM/closea.F90

    r9161 r9169  
    123123         ENDIF 
    124124      ELSE  
    125          IF( lwp ) WRITE(numout,*) 'closea_mask field not found in domain_cfg file. No closed seas defined.' 
     125         IF( lwp ) WRITE(numout,*) 
     126         IF( lwp ) WRITE(numout,*) '   ==>>>   closea_mask field not found in domain_cfg file.' 
     127         IF( lwp ) WRITE(numout,*) '           No closed seas defined.' 
     128         IF( lwp ) WRITE(numout,*) 
    126129         l_sbc_clo = .false. 
    127130         jncs = 0  
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/DOM/dom_oce.F90

    r9161 r9169  
    3131   !                                   !!* Namelist namdom : time & space domain * 
    3232   LOGICAL , PUBLIC ::   ln_linssh      !: =T  linear free surface ==>> model level are fixed in time 
    33    INTEGER , PUBLIC ::   nn_msh         !: >0  create a mesh-mask file (mesh_mask.nc) 
     33   LOGICAL , PUBLIC ::   ln_meshmask    !: =T  create a mesh-mask file (mesh_mask.nc) 
    3434   REAL(wp), PUBLIC ::   rn_isfhmin     !: threshold to discriminate grounded ice to floating ice 
    3535   REAL(wp), PUBLIC ::   rn_rdt         !: time step for the dynamics and tracer 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/DOM/domain.F90

    r9168 r9169  
    7070      !!                         and scale factors, and the coriolis factor 
    7171      !!              - dom_zgr: define the vertical coordinate and the bathymetry 
    72       !!              - dom_wri: create the meshmask file if nn_msh=1 
     72      !!              - dom_wri: create the meshmask file (ln_meshmask=T) 
    7373      !!              - 1D configuration, move Coriolis, u and v at T-point 
    7474      !!---------------------------------------------------------------------- 
     
    110110         END SELECT 
    111111         WRITE(numout,*)     '      Ocean model configuration used:' 
    112          WRITE(numout,*)     '              cn_cfg = ', cn_cfg 
    113          WRITE(numout,*)     '              nn_cfg = ', nn_cfg 
     112         WRITE(numout,*)     '         cn_cfg = ', TRIM( cn_cfg ), '   nn_cfg = ', nn_cfg 
    114113      ENDIF 
    115114      ! 
     
    176175      IF( lk_c1d         )   CALL cor_c1d       ! 1D configuration: Coriolis set at T-point 
    177176      ! 
    178       IF( nn_msh > 0 .AND. .NOT. ln_iscpl )                         CALL dom_wri      ! Create a domain file 
    179       IF( nn_msh > 0 .AND.       ln_iscpl .AND. .NOT. ln_rstart )   CALL dom_wri      ! Create a domain file 
    180       IF( .NOT.ln_rstart )   CALL dom_ctl       ! Domain control 
    181       ! 
    182        
     177      IF( ln_meshmask .AND. .NOT.ln_iscpl )                        CALL dom_wri     ! Create a domain file 
     178      IF( ln_meshmask .AND.      ln_iscpl .AND. .NOT.ln_rstart )   CALL dom_wri     ! Create a domain file 
     179      IF(                                       .NOT.ln_rstart )   CALL dom_ctl     ! Domain control 
     180      ! 
     181      IF( ln_write_cfg )   CALL cfg_write         ! create the configuration file 
     182      ! 
    183183      IF(lwp) THEN 
    184184         WRITE(numout,*) 
    185          WRITE(numout,*) 'dom_init : end of domain initialization nn_msh=', nn_msh 
     185         WRITE(numout,*) 'dom_init :   ==>>>   END of domain initialization' 
     186         WRITE(numout,*) '~~~~~~~~' 
    186187         WRITE(numout,*)  
    187188      ENDIF 
    188       ! 
    189       IF( ln_write_cfg )   CALL cfg_write         ! create the configuration file 
    190189      ! 
    191190   END SUBROUTINE dom_init 
     
    269268      !!---------------------------------------------------------------------- 
    270269      USE ioipsl 
     270      !! 
     271      INTEGER  ::   ios   ! Local integer 
     272      ! 
    271273      NAMELIST/namrun/ cn_ocerst_indir, cn_ocerst_outdir, nn_stocklist, ln_rst_list,                 & 
    272274         &             nn_no   , cn_exp   , cn_ocerst_in, cn_ocerst_out, ln_rstart , nn_rstctl ,     & 
     
    274276         &             nn_stock, nn_write , ln_mskland  , ln_clobber   , nn_chunksz, nn_euler  ,     & 
    275277         &             ln_cfmeta, ln_iscpl 
    276       NAMELIST/namdom/ ln_linssh, nn_msh, rn_isfhmin, rn_rdt, rn_atfp, ln_crs 
     278      NAMELIST/namdom/ ln_linssh, rn_isfhmin, rn_rdt, rn_atfp, ln_crs, ln_meshmask 
    277279#if defined key_netcdf4 
    278280      NAMELIST/namnc4/ nn_nchunks_i, nn_nchunks_j, nn_nchunks_k, ln_nc4zip 
    279281#endif 
    280       INTEGER  ::   ios                 ! Local integer output status for namelist read 
    281       !!---------------------------------------------------------------------- 
     282      !!---------------------------------------------------------------------- 
     283      ! 
     284      IF(lwp) THEN 
     285         WRITE(numout,*) 
     286         WRITE(numout,*) 'dom_nam  : domain initialization through namelist read' 
     287         WRITE(numout,*) '~~~~~~~ ' 
     288      ENDIF 
    282289      ! 
    283290      REWIND( numnam_ref )              ! Namelist namrun in reference namelist : Parameters of the run 
     
    290297      ! 
    291298      IF(lwp) THEN                  ! control print 
    292          WRITE(numout,*) 
    293          WRITE(numout,*) 'dom_nam  : domain initialization through namelist read' 
    294          WRITE(numout,*) '~~~~~~~ ' 
    295          WRITE(numout,*) '   Namelist namrun' 
    296          WRITE(numout,*) '      job number                      nn_no      = ', nn_no 
    297          WRITE(numout,*) '      experiment name for output      cn_exp     = ', cn_exp 
    298          WRITE(numout,*) '      file prefix restart input       cn_ocerst_in= ', cn_ocerst_in 
    299          WRITE(numout,*) '      restart input directory         cn_ocerst_indir= ', cn_ocerst_indir 
    300          WRITE(numout,*) '      file prefix restart output      cn_ocerst_out= ', cn_ocerst_out 
    301          WRITE(numout,*) '      restart output directory        cn_ocerst_outdir= ', cn_ocerst_outdir 
    302          WRITE(numout,*) '      restart logical                 ln_rstart  = ', ln_rstart 
    303          WRITE(numout,*) '      start with forward time step    nn_euler   = ', nn_euler 
    304          WRITE(numout,*) '      control of time step            nn_rstctl  = ', nn_rstctl 
    305          WRITE(numout,*) '      number of the first time step   nn_it000   = ', nn_it000 
    306          WRITE(numout,*) '      number of the last time step    nn_itend   = ', nn_itend 
    307          WRITE(numout,*) '      initial calendar date aammjj    nn_date0   = ', nn_date0 
    308          WRITE(numout,*) '      initial time of day in hhmm     nn_time0   = ', nn_time0 
    309          WRITE(numout,*) '      leap year calendar (0/1)        nn_leapy   = ', nn_leapy 
    310          WRITE(numout,*) '      initial state output            nn_istate  = ', nn_istate 
     299         WRITE(numout,*) '   Namelist : namrun' 
     300         WRITE(numout,*) '      job number                      nn_no           = ', nn_no 
     301         WRITE(numout,*) '      experiment name for output      cn_exp          = ', TRIM( cn_exp           ) 
     302         WRITE(numout,*) '      file prefix restart input       cn_ocerst_in    = ', TRIM( cn_ocerst_in     ) 
     303         WRITE(numout,*) '      restart input directory         cn_ocerst_indir = ', TRIM( cn_ocerst_indir  ) 
     304         WRITE(numout,*) '      file prefix restart output      cn_ocerst_out   = ', TRIM( cn_ocerst_out    ) 
     305         WRITE(numout,*) '      restart output directory        cn_ocerst_outdir= ', TRIM( cn_ocerst_outdir ) 
     306         WRITE(numout,*) '      restart logical                 ln_rstart       = ', ln_rstart 
     307         WRITE(numout,*) '      start with forward time step    nn_euler        = ', nn_euler 
     308         WRITE(numout,*) '      control of time step            nn_rstctl       = ', nn_rstctl 
     309         WRITE(numout,*) '      number of the first time step   nn_it000        = ', nn_it000 
     310         WRITE(numout,*) '      number of the last time step    nn_itend        = ', nn_itend 
     311         WRITE(numout,*) '      initial calendar date aammjj    nn_date0        = ', nn_date0 
     312         WRITE(numout,*) '      initial time of day in hhmm     nn_time0        = ', nn_time0 
     313         WRITE(numout,*) '      leap year calendar (0/1)        nn_leapy        = ', nn_leapy 
     314         WRITE(numout,*) '      initial state output            nn_istate       = ', nn_istate 
    311315         IF( ln_rst_list ) THEN 
    312             WRITE(numout,*) '      list of restart dump times      nn_stocklist   =', nn_stocklist 
     316            WRITE(numout,*) '      list of restart dump times      nn_stocklist    =', nn_stocklist 
    313317         ELSE 
    314             WRITE(numout,*) '      frequency of restart file       nn_stock   = ', nn_stock 
     318            WRITE(numout,*) '      frequency of restart file       nn_stock        = ', nn_stock 
    315319         ENDIF 
    316          WRITE(numout,*) '      frequency of output file        nn_write   = ', nn_write 
    317          WRITE(numout,*) '      mask land points                ln_mskland = ', ln_mskland 
    318          WRITE(numout,*) '      additional CF standard metadata ln_cfmeta  = ', ln_cfmeta 
    319          WRITE(numout,*) '      overwrite an existing file      ln_clobber = ', ln_clobber 
    320          WRITE(numout,*) '      NetCDF chunksize (bytes)        nn_chunksz = ', nn_chunksz 
    321          WRITE(numout,*) '      IS coupling at the restart step ln_iscpl   = ', ln_iscpl 
     320         WRITE(numout,*) '      frequency of output file        nn_write        = ', nn_write 
     321         WRITE(numout,*) '      mask land points                ln_mskland      = ', ln_mskland 
     322         WRITE(numout,*) '      additional CF standard metadata ln_cfmeta       = ', ln_cfmeta 
     323         WRITE(numout,*) '      overwrite an existing file      ln_clobber      = ', ln_clobber 
     324         WRITE(numout,*) '      NetCDF chunksize (bytes)        nn_chunksz      = ', nn_chunksz 
     325         WRITE(numout,*) '      IS coupling at the restart step ln_iscpl        = ', ln_iscpl 
    322326      ENDIF 
    323327 
     
    336340      IF( neuler == 1 .AND. .NOT. ln_rstart ) THEN 
    337341         IF(lwp) WRITE(numout,*)   
    338          IF(lwp) WRITE(numout,*)'   Start from rest (ln_rstart=F) ==>>> an Euler initial time step is used,' 
    339          IF(lwp) WRITE(numout,*)'                                       nn_euler is forced to 0 '    
     342         IF(lwp) WRITE(numout,*)'   ==>>>   Start from rest (ln_rstart=F)' 
     343         IF(lwp) WRITE(numout,*)'           an Euler initial time step is used : nn_euler is forced to 0 '    
    340344         neuler = 0 
    341345      ENDIF 
    342346      !                             ! control of output frequency 
    343       IF ( nstock == 0 .OR. nstock > nitend ) THEN 
     347      IF( nstock == 0 .OR. nstock > nitend ) THEN 
    344348         WRITE(ctmp1,*) 'nstock = ', nstock, ' it is forced to ', nitend 
    345349         CALL ctl_warn( ctmp1 ) 
     
    376380      READ  ( numnam_cfg, namdom, IOSTAT = ios, ERR = 904 ) 
    377381904   IF( ios >  0 )   CALL ctl_nam ( ios , 'namdom in configuration namelist', lwp ) 
    378       IF(lwm) WRITE ( numond, namdom ) 
     382      IF(lwm) WRITE( numond, namdom ) 
    379383      ! 
    380384      IF(lwp) THEN 
    381385         WRITE(numout,*) 
    382          WRITE(numout,*) '   Namelist namdom : space & time domain' 
    383          WRITE(numout,*) '      linear free surface (=T)              ln_linssh  = ', ln_linssh 
    384          WRITE(numout,*) '      create mesh/mask file(s)              nn_msh     = ', nn_msh 
    385          WRITE(numout,*) '           = 0   no file created           ' 
    386          WRITE(numout,*) '           = 1   mesh_mask                 ' 
    387          WRITE(numout,*) '           = 2   mesh and mask             ' 
    388          WRITE(numout,*) '           = 3   mesh_hgr, msh_zgr and mask' 
    389          WRITE(numout,*) '      treshold to open the isf cavity       rn_isfhmin = ', rn_isfhmin, ' (m)' 
    390          WRITE(numout,*) '      ocean time step                       rn_rdt     = ', rn_rdt 
    391          WRITE(numout,*) '      asselin time filter parameter         rn_atfp    = ', rn_atfp 
    392          WRITE(numout,*) '      online coarsening of dynamical fields ln_crs     = ', ln_crs 
    393       ENDIF 
    394        
    395       call flush( numout ) 
    396       ! 
    397 !     !          ! conversion DOCTOR names into model names (this should disappear soon) 
    398       atfp      = rn_atfp 
    399       rdt       = rn_rdt 
     386         WRITE(numout,*) '   Namelist : namdom   ---   space & time domain' 
     387         WRITE(numout,*) '      linear free surface (=T)                ln_linssh   = ', ln_linssh 
     388         WRITE(numout,*) '      create mesh/mask file                   ln_meshmask = ', ln_meshmask 
     389         WRITE(numout,*) '      treshold to open the isf cavity         rn_isfhmin  = ', rn_isfhmin, ' [m]' 
     390         WRITE(numout,*) '      ocean time step                         rn_rdt      = ', rn_rdt 
     391         WRITE(numout,*) '      asselin time filter parameter           rn_atfp     = ', rn_atfp 
     392         WRITE(numout,*) '      online coarsening of dynamical fields   ln_crs      = ', ln_crs 
     393      ENDIF 
     394      ! 
     395      !          ! conversion DOCTOR names into model names (this should disappear soon) 
     396      atfp = rn_atfp 
     397      rdt  = rn_rdt 
    400398 
    401399#if defined key_netcdf4 
     
    403401      REWIND( numnam_ref )              ! Namelist namnc4 in reference namelist : NETCDF 
    404402      READ  ( numnam_ref, namnc4, IOSTAT = ios, ERR = 907) 
    405 907   IF( ios /= 0 ) CALL ctl_nam ( ios , 'namnc4 in reference namelist', lwp ) 
     403907   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namnc4 in reference namelist', lwp ) 
    406404      REWIND( numnam_cfg )              ! Namelist namnc4 in configuration namelist : NETCDF 
    407405      READ  ( numnam_cfg, namnc4, IOSTAT = ios, ERR = 908 ) 
    408 908   IF( ios >  0 ) CALL ctl_nam ( ios , 'namnc4 in configuration namelist', lwp ) 
     406908   IF( ios >  0 )   CALL ctl_nam ( ios , 'namnc4 in configuration namelist', lwp ) 
    409407      IF(lwm) WRITE( numond, namnc4 ) 
    410408 
     
    412410         WRITE(numout,*) 
    413411         WRITE(numout,*) '   Namelist namnc4 - Netcdf4 chunking parameters' 
    414          WRITE(numout,*) '      number of chunks in i-dimension      nn_nchunks_i  = ', nn_nchunks_i 
    415          WRITE(numout,*) '      number of chunks in j-dimension      nn_nchunks_j  = ', nn_nchunks_j 
    416          WRITE(numout,*) '      number of chunks in k-dimension      nn_nchunks_k  = ', nn_nchunks_k 
    417          WRITE(numout,*) '      apply netcdf4/hdf5 chunking & compression ln_nc4zip = ', ln_nc4zip 
     412         WRITE(numout,*) '      number of chunks in i-dimension             nn_nchunks_i = ', nn_nchunks_i 
     413         WRITE(numout,*) '      number of chunks in j-dimension             nn_nchunks_j = ', nn_nchunks_j 
     414         WRITE(numout,*) '      number of chunks in k-dimension             nn_nchunks_k = ', nn_nchunks_k 
     415         WRITE(numout,*) '      apply netcdf4/hdf5 chunking & compression   ln_nc4zip    = ', ln_nc4zip 
    418416      ENDIF 
    419417 
     
    487485      !! ** Purpose :   read the domain size in domain configuration file 
    488486      !! 
    489       !! ** Method  :    
    490       !! 
     487      !! ** Method  :   read the cn_domcfg NetCDF file 
    491488      !!---------------------------------------------------------------------- 
    492489      CHARACTER(len=*), DIMENSION(:), INTENT(out) ::   ldtxt           ! stored print information 
     
    503500      ii = 1 
    504501      WRITE(ldtxt(ii),*) '           '                                                    ;   ii = ii+1 
    505       WRITE(ldtxt(ii),*) 'domain_cfg : domain size read in ', TRIM( cn_domcfg ), ' file'   ;   ii = ii+1 
     502      WRITE(ldtxt(ii),*) 'domain_cfg : domain size read in ', TRIM( cn_domcfg ), ' file'  ;   ii = ii+1 
    506503      WRITE(ldtxt(ii),*) '~~~~~~~~~~ '                                                    ;   ii = ii+1 
    507504      ! 
     
    515512         CALL iom_get( inum, 'ORCA_index', zorca_res )   ;   kk_cfg = INT( zorca_res ) 
    516513         ! 
    517          WRITE(ldtxt(ii),*) '       '                                                    ;   ii = ii+1 
    518          WRITE(ldtxt(ii),*) '       ==>>>   ORCA configuration '                         ;   ii = ii+1 
    519          WRITE(ldtxt(ii),*) '       '                                                    ;   ii = ii+1 
     514         WRITE(ldtxt(ii),*) '       '                                                     ;   ii = ii+1 
     515         WRITE(ldtxt(ii),*) '       ==>>>   ORCA configuration '                          ;   ii = ii+1 
     516         WRITE(ldtxt(ii),*) '       '                                                     ;   ii = ii+1 
    520517         ! 
    521518      ELSE                                !- cd_cfg & k_cfg are not used 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/DOM/domhgr.F90

    r9019 r9169  
    9191      IF( ln_read_cfg ) THEN        !==  read in mesh_mask.nc file  ==! 
    9292         IF(lwp) WRITE(numout,*) 
    93          IF(lwp) WRITE(numout,*) '          read horizontal mesh in ', TRIM( cn_domcfg ), ' file' 
     93         IF(lwp) WRITE(numout,*) '   ==>>>   read horizontal mesh in ', TRIM( cn_domcfg ), ' file' 
    9494         ! 
    9595         CALL hgr_read   ( glamt , glamu , glamv , glamf ,   &    ! geographic position (required) 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/DOM/dommsk.F90

    r9168 r9169  
    119119         WRITE(numout,*) '      consistency with analytical form   ln_vorlat = ',ln_vorlat  
    120120      ENDIF 
    121  
    122       IF     (      rn_shlat == 0.               ) THEN   ;   IF(lwp) WRITE(numout,*) '   ocean lateral  free-slip ' 
    123       ELSEIF (      rn_shlat == 2.               ) THEN   ;   IF(lwp) WRITE(numout,*) '   ocean lateral  no-slip ' 
    124       ELSEIF ( 0. < rn_shlat .AND. rn_shlat < 2. ) THEN   ;   IF(lwp) WRITE(numout,*) '   ocean lateral  partial-slip ' 
    125       ELSEIF ( 2. < rn_shlat                     ) THEN   ;   IF(lwp) WRITE(numout,*) '   ocean lateral  strong-slip ' 
     121      ! 
     122      IF(lwp) WRITE(numout,*) 
     123      IF     (      rn_shlat == 0.               ) THEN   ;   IF(lwp) WRITE(numout,*) '   ==>>>   ocean lateral  free-slip' 
     124      ELSEIF (      rn_shlat == 2.               ) THEN   ;   IF(lwp) WRITE(numout,*) '   ==>>>   ocean lateral  no-slip' 
     125      ELSEIF ( 0. < rn_shlat .AND. rn_shlat < 2. ) THEN   ;   IF(lwp) WRITE(numout,*) '   ==>>>   ocean lateral  partial-slip' 
     126      ELSEIF ( 2. < rn_shlat                     ) THEN   ;   IF(lwp) WRITE(numout,*) '   ==>>>   ocean lateral  strong-slip' 
    126127      ELSE 
    127128         WRITE(ctmp1,*) ' rn_shlat is negative = ', rn_shlat 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/DOM/domwri.F90

    r9124 r9169  
    4949      !!      diagnostic computation. 
    5050      !! 
    51       !! ** Method  :   Write in a file all the arrays generated in routines 
    52       !!      domhgr, domzgr, and dommsk. Note: the file contain depends on 
    53       !!      the vertical coord. used (z-coord, partial steps, s-coord) 
    54       !!            MOD(nn_msh, 3) = 1  :   'mesh_mask.nc' file 
    55       !!                         = 2  :   'mesh.nc' and mask.nc' files 
    56       !!                         = 0  :   'mesh_hgr.nc', 'mesh_zgr.nc' and 
    57       !!                                  'mask.nc' files 
    58       !!      For huge size domain, use option 2 or 3 depending on your  
    59       !!      vertical coordinate. 
    60       !! 
    61       !!      if     nn_msh <= 3: write full 3D arrays for e3[tuvw] and gdep[tuvw] 
    62       !!      if 3 < nn_msh <= 6: write full 3D arrays for e3[tuvw] and 2D arrays  
    63       !!                        corresponding to the depth of the bottom t- and w-points 
    64       !!      if 6 < nn_msh <= 9: write 2D arrays corresponding to the depth and the 
    65       !!                        thickness (e3[tw]_ps) of the bottom points  
     51      !! ** Method  :   create a file with all domain related arrays 
    6652      !! 
    6753      !! ** output file :   meshmask.nc  : domain size, horizontal grid-point position, 
     
    196182      CALL iom_close( inum )                !        close the files  
    197183      !                                     ! ============================ 
    198       ! 
    199184   END SUBROUTINE dom_wri 
    200185 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/DOM/domzgr.F90

    r9161 r9169  
    8787      IF( ln_read_cfg ) THEN        !==  read in mesh_mask.nc file  ==! 
    8888         IF(lwp) WRITE(numout,*) 
    89          IF(lwp) WRITE(numout,*) '          Read vertical mesh in ', TRIM( cn_domcfg ), ' file' 
     89         IF(lwp) WRITE(numout,*) '   ==>>>   Read vertical mesh in ', TRIM( cn_domcfg ), ' file' 
    9090         ! 
    9191         CALL zgr_read   ( ln_zco  , ln_zps  , ln_sco, ln_isfcav,   &  
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/DOM/iscplrst.F90

    r9090 r9169  
    7777          
    7878      !                       ! create  a domain file 
    79       IF( nn_msh /= 0 .AND. ln_iscpl )   CALL dom_wri 
     79      IF( ln_meshmask .AND. ln_iscpl )   CALL dom_wri 
    8080      ! 
    8181      IF ( ln_hsb ) THEN 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/DOM/phycst.F90

    r9019 r9169  
    113113      ! ------------------------ 
    114114      IF(lwp) WRITE(numout,*) 
    115       IF(lwp) WRITE(numout,*) '       Constants' 
     115      IF(lwp) WRITE(numout,*) '   Constants' 
    116116 
    117117      IF(lwp) WRITE(numout,*) 
    118       IF(lwp) WRITE(numout,*) '          mathematical constant                 rpi = ', rpi 
     118      IF(lwp) WRITE(numout,*) '      mathematical constant                 rpi = ', rpi 
    119119 
    120120      rsiyea = 365.25_wp * rday * 2._wp * rpi / 6.283076_wp 
     
    126126#endif 
    127127      IF(lwp) WRITE(numout,*) 
    128       IF(lwp) WRITE(numout,*) '          day                                rday   = ', rday,   ' s' 
    129       IF(lwp) WRITE(numout,*) '          sideral year                       rsiyea = ', rsiyea, ' s' 
    130       IF(lwp) WRITE(numout,*) '          sideral day                        rsiday = ', rsiday, ' s' 
    131       IF(lwp) WRITE(numout,*) '          omega                              omega  = ', omega,  ' s^-1' 
    132  
     128      IF(lwp) WRITE(numout,*) '      day                                rday   = ', rday,   ' s' 
     129      IF(lwp) WRITE(numout,*) '      sideral year                       rsiyea = ', rsiyea, ' s' 
     130      IF(lwp) WRITE(numout,*) '      sideral day                        rsiday = ', rsiday, ' s' 
     131      IF(lwp) WRITE(numout,*) '      omega                              omega  = ', omega,  ' s^-1' 
    133132      IF(lwp) WRITE(numout,*) 
    134       IF(lwp) WRITE(numout,*) '          nb of months per year               raamo = ', raamo, ' months' 
    135       IF(lwp) WRITE(numout,*) '          nb of hours per day                 rjjhh = ', rjjhh, ' hours' 
    136       IF(lwp) WRITE(numout,*) '          nb of minutes per hour              rhhmm = ', rhhmm, ' mn' 
    137       IF(lwp) WRITE(numout,*) '          nb of seconds per minute            rmmss = ', rmmss, ' s' 
    138  
     133      IF(lwp) WRITE(numout,*) '      nb of months per year               raamo = ', raamo, ' months' 
     134      IF(lwp) WRITE(numout,*) '      nb of hours per day                 rjjhh = ', rjjhh, ' hours' 
     135      IF(lwp) WRITE(numout,*) '      nb of minutes per hour              rhhmm = ', rhhmm, ' mn' 
     136      IF(lwp) WRITE(numout,*) '      nb of seconds per minute            rmmss = ', rmmss, ' s' 
    139137      IF(lwp) WRITE(numout,*) 
    140       IF(lwp) WRITE(numout,*) '          earth radius                         ra   = ', ra, ' m' 
    141       IF(lwp) WRITE(numout,*) '          gravity                              grav = ', grav , ' m/s^2' 
    142  
     138      IF(lwp) WRITE(numout,*) '      earth radius                         ra   = ', ra, ' m' 
     139      IF(lwp) WRITE(numout,*) '      gravity                              grav = ', grav , ' m/s^2' 
    143140      IF(lwp) WRITE(numout,*) 
    144       IF(lwp) WRITE(numout,*) '          triple point of temperature      rtt      = ', rtt     , ' K' 
    145       IF(lwp) WRITE(numout,*) '          freezing point of water          rt0      = ', rt0     , ' K' 
    146       IF(lwp) WRITE(numout,*) '          melting point of snow            rt0_snow = ', rt0_snow, ' K' 
    147       IF(lwp) WRITE(numout,*) '          melting point of ice             rt0_ice  = ', rt0_ice , ' K' 
    148  
    149       IF(lwp) WRITE(numout,*) '          reference density and heat capacity now defined in eosbn2.f90' 
     141      IF(lwp) WRITE(numout,*) '      triple point of temperature      rtt      = ', rtt     , ' K' 
     142      IF(lwp) WRITE(numout,*) '      freezing point of water          rt0      = ', rt0     , ' K' 
     143      IF(lwp) WRITE(numout,*) '      melting point of snow            rt0_snow = ', rt0_snow, ' K' 
     144      IF(lwp) WRITE(numout,*) '      melting point of ice             rt0_ice  = ', rt0_ice , ' K' 
     145      IF(lwp) WRITE(numout,*) 
     146      IF(lwp) WRITE(numout,*) '   reference density and heat capacity now defined in eosbn2.f90' 
    150147               
    151148#if defined key_lim3 || defined key_cice 
     
    163160         WRITE(numout,*) 
    164161#if defined key_cice 
    165          WRITE(numout,*) '          thermal conductivity of the snow          = ', rcdsn   , ' J/s/m/K' 
     162         WRITE(numout,*) '      thermal conductivity of the snow          = ', rcdsn   , ' J/s/m/K' 
    166163#endif 
    167          WRITE(numout,*) '          thermal conductivity of pure ice          = ', rcdic   , ' J/s/m/K' 
    168          WRITE(numout,*) '          fresh ice specific heat                   = ', cpic    , ' J/kg/K' 
    169          WRITE(numout,*) '          latent heat of fusion of fresh ice / snow = ', lfus    , ' J/kg' 
     164         WRITE(numout,*) '      thermal conductivity of pure ice          = ', rcdic   , ' J/s/m/K' 
     165         WRITE(numout,*) '      fresh ice specific heat                   = ', cpic    , ' J/kg/K' 
     166         WRITE(numout,*) '      latent heat of fusion of fresh ice / snow = ', lfus    , ' J/kg' 
    170167#if defined key_lim3 || defined key_cice 
    171          WRITE(numout,*) '          latent heat of subl.  of fresh ice / snow = ', lsub    , ' J/kg' 
     168         WRITE(numout,*) '      latent heat of subl.  of fresh ice / snow = ', lsub    , ' J/kg' 
    172169#else 
    173          WRITE(numout,*) '          density times specific heat for snow      = ', rcpsn   , ' J/m^3/K'  
    174          WRITE(numout,*) '          density times specific heat for ice       = ', rcpic   , ' J/m^3/K' 
    175          WRITE(numout,*) '          volumetric latent heat fusion of sea ice  = ', xlic    , ' J/m'  
    176          WRITE(numout,*) '          latent heat of sublimation of snow        = ', xsn     , ' J/kg'  
     170         WRITE(numout,*) '      density times specific heat for snow      = ', rcpsn   , ' J/m^3/K'  
     171         WRITE(numout,*) '      density times specific heat for ice       = ', rcpic   , ' J/m^3/K' 
     172         WRITE(numout,*) '      volumetric latent heat fusion of sea ice  = ', xlic    , ' J/m'  
     173         WRITE(numout,*) '      latent heat of sublimation of snow        = ', xsn     , ' J/kg'  
    177174#endif 
    178          WRITE(numout,*) '          volumetric latent heat fusion of snow     = ', xlsn    , ' J/m^3'  
    179          WRITE(numout,*) '          density of sea ice                        = ', rhoic   , ' kg/m^3' 
    180          WRITE(numout,*) '          density of snow                           = ', rhosn   , ' kg/m^3' 
    181          WRITE(numout,*) '          density of freshwater (in melt ponds)     = ', rhofw   , ' kg/m^3' 
    182          WRITE(numout,*) '          emissivity of snow or ice                 = ', emic   
    183          WRITE(numout,*) '          salinity of ice                           = ', sice    , ' psu' 
    184          WRITE(numout,*) '          salinity of sea                           = ', soce    , ' psu' 
    185          WRITE(numout,*) '          latent heat of evaporation (water)        = ', cevap   , ' J/m^3'  
    186          WRITE(numout,*) '          correction factor for solar radiation     = ', srgamma  
    187          WRITE(numout,*) '          von Karman constant                       = ', vkarmn  
    188          WRITE(numout,*) '          Stefan-Boltzmann constant                 = ', stefan  , ' J/s/m^2/K^4' 
     175         WRITE(numout,*) '      volumetric latent heat fusion of snow     = ', xlsn    , ' J/m^3'  
     176         WRITE(numout,*) '      density of sea ice                        = ', rhoic   , ' kg/m^3' 
     177         WRITE(numout,*) '      density of snow                           = ', rhosn   , ' kg/m^3' 
     178         WRITE(numout,*) '      density of freshwater (in melt ponds)     = ', rhofw   , ' kg/m^3' 
     179         WRITE(numout,*) '      emissivity of snow or ice                 = ', emic   
     180         WRITE(numout,*) '      salinity of ice                           = ', sice    , ' psu' 
     181         WRITE(numout,*) '      salinity of sea                           = ', soce    , ' psu' 
     182         WRITE(numout,*) '      latent heat of evaporation (water)        = ', cevap   , ' J/m^3'  
     183         WRITE(numout,*) '      correction factor for solar radiation     = ', srgamma  
     184         WRITE(numout,*) '      von Karman constant                       = ', vkarmn  
     185         WRITE(numout,*) '      Stefan-Boltzmann constant                 = ', stefan  , ' J/s/m^2/K^4' 
    189186         WRITE(numout,*) 
    190          WRITE(numout,*) '          conversion: degre ==> radian          rad = ', rad 
     187         WRITE(numout,*) '      conversion: degre ==> radian          rad = ', rad 
    191188         WRITE(numout,*) 
    192          WRITE(numout,*) '          smallest real computer value       rsmall = ', rsmall 
     189         WRITE(numout,*) '      smallest real computer value       rsmall = ', rsmall 
    193190      ENDIF 
    194191 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg.F90

    r9168 r9169  
    194194      !!---------------------------------------------------------------------- 
    195195      ! 
     196      IF(lwp) THEN 
     197         WRITE(numout,*) 
     198         WRITE(numout,*) 'dyn_spg_init : choice of the surface pressure gradient scheme' 
     199         WRITE(numout,*) '~~~~~~~~~~~~' 
     200      ENDIF 
     201      ! 
    196202      REWIND( numnam_ref )              ! Namelist namdyn_spg in reference namelist : Free surface 
    197203      READ  ( numnam_ref, namdyn_spg, IOSTAT = ios, ERR = 901) 
     
    204210      ! 
    205211      IF(lwp) THEN             ! Namelist print 
    206          WRITE(numout,*) 
    207          WRITE(numout,*) 'dyn_spg_init : choice of the surface pressure gradient scheme' 
    208          WRITE(numout,*) '~~~~~~~~~~~' 
    209          WRITE(numout,*) '     Explicit free surface                  ln_dynspg_exp = ', ln_dynspg_exp 
    210          WRITE(numout,*) '     Free surface with time splitting       ln_dynspg_ts  = ', ln_dynspg_ts 
     212         WRITE(numout,*) '   Namelist : namdyn_spg                    ' 
     213         WRITE(numout,*) '      Explicit free surface                  ln_dynspg_exp = ', ln_dynspg_exp 
     214         WRITE(numout,*) '      Free surface with time splitting       ln_dynspg_ts  = ', ln_dynspg_ts 
    211215      ENDIF 
    212216      !                          ! Control of surface pressure gradient scheme options 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/DYN/dynspg_ts.F90

    r9124 r9169  
    14241424      ! Print results 
    14251425      IF(lwp) WRITE(numout,*) 
    1426       IF(lwp) WRITE(numout,*) 'dyn_spg_ts : split-explicit free surface' 
    1427       IF(lwp) WRITE(numout,*) '~~~~~~~~~~' 
     1426      IF(lwp) WRITE(numout,*) 'dyn_spg_ts_init : split-explicit free surface' 
     1427      IF(lwp) WRITE(numout,*) '~~~~~~~~~~~~~~~' 
    14281428      IF( ln_bt_auto ) THEN 
    1429          IF(lwp) WRITE(numout,*) '     ln_ts_auto=.true. Automatically set nn_baro ' 
     1429         IF(lwp) WRITE(numout,*) '     ln_ts_auto =.true. Automatically set nn_baro ' 
    14301430         IF(lwp) WRITE(numout,*) '     Max. courant number allowed: ', rn_bt_cmax 
    14311431      ELSE 
    1432          IF(lwp) WRITE(numout,*) '     ln_ts_auto=.false.: Use nn_baro in namelist ' 
     1432         IF(lwp) WRITE(numout,*) '     ln_ts_auto=.false.: Use nn_baro in namelist   nn_baro = ', nn_baro 
    14331433      ENDIF 
    14341434 
    14351435      IF(ln_bt_av) THEN 
    1436          IF(lwp) WRITE(numout,*) '     ln_bt_av=.true.  => Time averaging over nn_baro time steps is on ' 
     1436         IF(lwp) WRITE(numout,*) '     ln_bt_av =.true.  ==> Time averaging over nn_baro time steps is on ' 
    14371437      ELSE 
    1438          IF(lwp) WRITE(numout,*) '     ln_bt_av=.false. => No time averaging of barotropic variables ' 
     1438         IF(lwp) WRITE(numout,*) '     ln_bt_av =.false. => No time averaging of barotropic variables ' 
    14391439      ENDIF 
    14401440      ! 
     
    14561456         CASE( 1 )      ;   IF(lwp) WRITE(numout,*) '           Boxcar: width = nn_baro' 
    14571457         CASE( 2 )      ;   IF(lwp) WRITE(numout,*) '           Boxcar: width = 2*nn_baro'  
    1458          CASE DEFAULT   ;   CALL ctl_stop( 'unrecognised value for nn_bt_flt: should 0,1,2' ) 
     1458         CASE DEFAULT   ;   CALL ctl_stop( 'unrecognised value for nn_bt_flt: should 0,1, or 2' ) 
    14591459      END SELECT 
    14601460      ! 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/LBC/mppini.F90

    r9168 r9169  
    229229         IF( jpnj  == 1             )   ibondj(ii,ij) = 2 
    230230         ibondi(ii,ij) = 0 
    231          IF( MOD(jarea,jpni) == 1 )   ibondi(ii,ij) = -1 
    232          IF( MOD(jarea,jpni) == 0 )   ibondi(ii,ij) =  1 
    233          IF( jpni            == 1 )   ibondi(ii,ij) =  2 
     231         IF( MOD(jarea,jpni) ==  1 )   ibondi(ii,ij) = -1 
     232         IF( MOD(jarea,jpni) ==  0 )   ibondi(ii,ij) =  1 
     233         IF( jpni            ==  1 )   ibondi(ii,ij) =  2 
    234234 
    235235         ! Subdomain neighbors 
     
    242242         ilei(ii,ij) = ili - nn_hls 
    243243 
    244          IF( ibondi(ii,ij) == -1 .OR. ibondi(ii,ij) == 2 ) ildi(ii,ij) =  1 
    245          IF( ibondi(ii,ij) ==  1 .OR. ibondi(ii,ij) == 2 ) ilei(ii,ij) = ili 
     244         IF( ibondi(ii,ij) == -1 .OR. ibondi(ii,ij) == 2 )   ildi(ii,ij) =  1 
     245         IF( ibondi(ii,ij) ==  1 .OR. ibondi(ii,ij) == 2 )   ilei(ii,ij) = ili 
    246246         ildj(ii,ij) =  1  + nn_hls 
    247247         ilej(ii,ij) = ilj - nn_hls 
    248          IF( ibondj(ii,ij) == -1 .OR. ibondj(ii,ij) == 2 ) ildj(ii,ij) =  1 
    249          IF( ibondj(ii,ij) ==  1 .OR. ibondj(ii,ij) == 2 ) ilej(ii,ij) = ilj 
     248         IF( ibondj(ii,ij) == -1 .OR. ibondj(ii,ij) == 2 )   ildj(ii,ij) =  1 
     249         IF( ibondj(ii,ij) ==  1 .OR. ibondj(ii,ij) == 2 )   ilej(ii,ij) = ilj 
    250250 
    251251         ! warning ii*ij (zone) /= nproc (processors)! 
     
    326326            il1 = il1+ifreq 
    327327         END DO 
    328  9400    FORMAT('     ***',20('*************',a3)) 
    329  9403    FORMAT('     *     ',20('         *   ',a3)) 
    330  9401    FORMAT('        ',20('   ',i3,'          ')) 
    331  9402    FORMAT(' ',i3,' *  ',20(i3,'  x',i3,'   *   ')) 
    332  9404    FORMAT('     *  ',20('      ',i3,'   *   ')) 
     328 9400    FORMAT('           ***'   ,20('*************',a3)    ) 
     329 9403    FORMAT('           *     ',20('         *   ',a3)    ) 
     330 9401    FORMAT('              '   ,20('   ',i3,'          ') ) 
     331 9402    FORMAT('       ',i3,' *  ',20(i3,'  x',i3,'   *   ') ) 
     332 9404    FORMAT('           *  '   ,20('      ',i3,'   *   ') ) 
    333333      ENDIF 
    334334 
     
    479479      IF(lwp) THEN 
    480480         WRITE(numout,*) 
    481          WRITE(numout,*) ' nproc  = ', nproc 
    482          WRITE(numout,*) ' nowe   = ', nowe  , ' noea   =  ', noea 
    483          WRITE(numout,*) ' nono   = ', nono  , ' noso   =  ', noso 
    484          WRITE(numout,*) ' nbondi = ', nbondi 
    485          WRITE(numout,*) ' nbondj = ', nbondj 
    486          WRITE(numout,*) ' npolj  = ', npolj 
    487          WRITE(numout,*) ' nperio = ', nperio 
    488          WRITE(numout,*) ' nlci   = ', nlci 
    489          WRITE(numout,*) ' nlcj   = ', nlcj 
    490          WRITE(numout,*) ' nimpp  = ', nimpp 
    491          WRITE(numout,*) ' njmpp  = ', njmpp 
    492          WRITE(numout,*) ' nreci  = ', nreci   
    493          WRITE(numout,*) ' nrecj  = ', nrecj   
    494          WRITE(numout,*) ' nn_hls = ', nn_hls  
     481         WRITE(numout,*) '   resulting internal parameters : ' 
     482         WRITE(numout,*) '      nproc  = ', nproc 
     483         WRITE(numout,*) '      nowe   = ', nowe  , '   noea  =  ', noea 
     484         WRITE(numout,*) '      nono   = ', nono  , '   noso  =  ', noso 
     485         WRITE(numout,*) '      nbondi = ', nbondi 
     486         WRITE(numout,*) '      nbondj = ', nbondj 
     487         WRITE(numout,*) '      npolj  = ', npolj 
     488         WRITE(numout,*) '      nperio = ', nperio 
     489         WRITE(numout,*) '      nlci   = ', nlci 
     490         WRITE(numout,*) '      nlcj   = ', nlcj 
     491         WRITE(numout,*) '      nimpp  = ', nimpp 
     492         WRITE(numout,*) '      njmpp  = ', njmpp 
     493         WRITE(numout,*) '      nreci  = ', nreci   
     494         WRITE(numout,*) '      nrecj  = ', nrecj   
     495         WRITE(numout,*) '      nn_hls = ', nn_hls  
    495496      ENDIF 
    496497  
    497       IF( nperio == 1 .AND. jpni /= 1 ) CALL ctl_stop( 'mpp_init: error on cyclicity' ) 
    498  
    499       IF( jperio == 7 .AND. ( jpni /= 1 .OR. jpnj /= 1 ) ) & 
     498      IF( nperio == 1 .AND. jpni /= 1 )   CALL ctl_stop( 'mpp_init: error on cyclicity' ) 
     499 
     500      IF( jperio == 7 .AND. ( jpni /= 1 .OR. jpnj /= 1 ) )   & 
    500501         &                  CALL ctl_stop( ' mpp_init: error jperio = 7 works only with jpni = jpnj = 1' ) 
    501502 
     
    503504      IF( jperio >= 3 .AND. jperio <= 6 .AND. jpni > 1 ) THEN 
    504505         CALL mpp_ini_north 
    505          IF(lwp) WRITE(numout,*) ' mpp_init : North fold boundary prepared for jpni >1' 
     506         IF(lwp) WRITE(numout,*) 
     507         IF(lwp) WRITE(numout,*) '   ==>>>   North fold boundary prepared for jpni >1' 
    506508      ENDIF 
    507509      ! 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/LDF/ldfdyn.F90

    r9168 r9169  
    142142      !                                ! Parameter control 
    143143      IF( ln_dynldf_NONE ) THEN 
    144          IF(lwp) WRITE(numout,*) '   No viscous operator selected. ahmt and ahmf are not allocated' 
     144         IF(lwp) WRITE(numout,*) '   ==>>>   No viscous operator selected. ahmt and ahmf are not allocated' 
    145145         l_ldfdyn_time = .FALSE. 
    146146         RETURN 
     
    173173         ! 
    174174         CASE(   0  )      !==  constant  ==! 
    175             IF(lwp) WRITE(numout,*) '          momentum mixing coef. = constant ' 
     175            IF(lwp) WRITE(numout,*) '   ==>>>   momentum mixing coef. = constant ' 
    176176            ahmt(:,:,:) = zah0 * tmask(:,:,:) 
    177177            ahmf(:,:,:) = zah0 * fmask(:,:,:) 
    178178            ! 
    179179         CASE(  10  )      !==  fixed profile  ==! 
    180             IF(lwp) WRITE(numout,*) '          momentum mixing coef. = F( depth )' 
     180            IF(lwp) WRITE(numout,*) '   ==>>>   momentum mixing coef. = F( depth )' 
    181181            ahmt(:,:,1) = zah0 * tmask(:,:,1)                      ! constant surface value 
    182182            ahmf(:,:,1) = zah0 * fmask(:,:,1) 
     
    184184            ! 
    185185         CASE ( -20 )      !== fixed horizontal shape read in file  ==! 
    186             IF(lwp) WRITE(numout,*) '          momentum mixing coef. = F(i,j) read in eddy_viscosity.nc file' 
     186            IF(lwp) WRITE(numout,*) '   ==>>>   momentum mixing coef. = F(i,j) read in eddy_viscosity.nc file' 
    187187            CALL iom_open( 'eddy_viscosity_2D.nc', inum ) 
    188188            CALL iom_get ( inum, jpdom_data, 'ahmt_2d', ahmt(:,:,1) ) 
     
    198198            ! 
    199199         CASE(  20  )      !== fixed horizontal shape  ==! 
    200             IF(lwp) WRITE(numout,*) '          momentum mixing coef. = F( e1, e2 ) or F( e1^3, e2^3 ) (lap. or blp. case)' 
     200            IF(lwp) WRITE(numout,*) '   ==>>>   momentum mixing coef. = F( e1, e2 ) or F( e1^3, e2^3 ) (lap. or blp. case)' 
    201201            IF( ln_dynldf_lap )   CALL ldf_c2d( 'DYN', 'LAP', zah0, ahmt, ahmf )    ! surface value proportional to scale factor 
    202202            IF( ln_dynldf_blp )   CALL ldf_c2d( 'DYN', 'BLP', zah0, ahmt, ahmf )    ! surface value proportional to scale factor^3 
    203203            ! 
    204204         CASE( -30  )      !== fixed 3D shape read in file  ==! 
    205             IF(lwp) WRITE(numout,*) '          momentum mixing coef. = F(i,j,k) read in eddy_diffusivity_3D.nc file' 
     205            IF(lwp) WRITE(numout,*) '   ==>>>   momentum mixing coef. = F(i,j,k) read in eddy_diffusivity_3D.nc file' 
    206206            CALL iom_open( 'eddy_viscosity_3D.nc', inum ) 
    207207            CALL iom_get ( inum, jpdom_data, 'ahmt_3d', ahmt ) 
     
    216216            ! 
    217217         CASE(  30  )       !==  fixed 3D shape  ==! 
    218             IF(lwp) WRITE(numout,*) '          momentum mixing coef. = F( latitude, longitude, depth )' 
     218            IF(lwp) WRITE(numout,*) '   ==>>>   momentum mixing coef. = F( latitude, longitude, depth )' 
    219219            IF( ln_dynldf_lap )   CALL ldf_c2d( 'DYN', 'LAP', zah0, ahmt, ahmf )    ! surface value proportional to scale factor 
    220220            IF( ln_dynldf_blp )   CALL ldf_c2d( 'DYN', 'BLP', zah0, ahmt, ahmf )    ! surface value proportional to scale factor 
     
    223223            ! 
    224224         CASE(  31  )       !==  time varying 3D field  ==! 
    225             IF(lwp) WRITE(numout,*) '          momentum mixing coef. = F( latitude, longitude, depth , time )' 
    226             IF(lwp) WRITE(numout,*) '                                proportional to the velocity : |u|e/12 or |u|e^3/12' 
     225            IF(lwp) WRITE(numout,*) '   ==>>>   momentum mixing coef. = F( latitude, longitude, depth , time )' 
     226            IF(lwp) WRITE(numout,*) '              proportional to the velocity : |u|e/12 or |u|e^3/12' 
    227227            ! 
    228228            l_ldfdyn_time = .TRUE.     ! will be calculated by call to ldf_dyn routine in step.F90 
    229229            ! 
    230230         CASE(  32  )       !==  time varying 3D field  ==! 
    231             IF(lwp) WRITE(numout,*) '          momentum mixing coef. = F( latitude, longitude, depth , time )' 
    232             IF(lwp) WRITE(numout,*) '             proportional to the local deformation rate and gridscale (Smagorinsky)' 
    233             IF(lwp) WRITE(numout,*) '                                                             : L^2|D| or L^4|D|/8' 
     231            IF(lwp) WRITE(numout,*) '   ==>>>   momentum mixing coef. = F( latitude, longitude, depth , time )' 
     232            IF(lwp) WRITE(numout,*) '              proportional to the local deformation rate and gridscale (Smagorinsky)' 
     233            IF(lwp) WRITE(numout,*) '                                                                : L^2|D| or L^4|D|/8' 
    234234            ! 
    235235            l_ldfdyn_time = .TRUE.     ! will be calculated by call to ldf_dyn routine in step.F90 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/LDF/ldftra.F90

    r9168 r9169  
    126126      !!---------------------------------------------------------------------- 
    127127      ! 
    128       !  Choice of lateral tracer physics 
    129       ! ================================= 
    130       ! 
    131       REWIND( numnam_ref )              ! Namelist namtra_ldf in reference namelist : Lateral physics on tracers 
    132       READ  ( numnam_ref, namtra_ldf, IOSTAT = ios, ERR = 901) 
    133 901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtra_ldf in reference namelist', lwp ) 
    134       ! 
    135       REWIND( numnam_cfg )              ! Namelist namtra_ldf in configuration namelist : Lateral physics on tracers 
    136       READ  ( numnam_cfg, namtra_ldf, IOSTAT = ios, ERR = 902 ) 
    137 902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namtra_ldf in configuration namelist', lwp ) 
    138       IF(lwm) WRITE ( numond, namtra_ldf ) 
    139       ! 
    140128      IF(lwp) THEN                      ! control print 
    141129         WRITE(numout,*) 
    142130         WRITE(numout,*) 'ldf_tra_init : lateral tracer physics' 
    143131         WRITE(numout,*) '~~~~~~~~~~~~ ' 
    144          WRITE(numout,*) '   Namelist namtra_ldf : lateral mixing parameters (type, direction, coefficients)' 
     132      ENDIF 
     133      ! 
     134      !  Choice of lateral tracer physics 
     135      ! ================================= 
     136      ! 
     137      REWIND( numnam_ref )              ! Namelist namtra_ldf in reference namelist : Lateral physics on tracers 
     138      READ  ( numnam_ref, namtra_ldf, IOSTAT = ios, ERR = 901) 
     139901   IF( ios /= 0 )   CALL ctl_nam ( ios , 'namtra_ldf in reference namelist', lwp ) 
     140      REWIND( numnam_cfg )              ! Namelist namtra_ldf in configuration namelist : Lateral physics on tracers 
     141      READ  ( numnam_cfg, namtra_ldf, IOSTAT = ios, ERR = 902 ) 
     142902   IF( ios >  0 )   CALL ctl_nam ( ios , 'namtra_ldf in configuration namelist', lwp ) 
     143      IF(lwm) WRITE( numond, namtra_ldf ) 
     144      ! 
     145      IF(lwp) THEN                      ! control print 
     146         WRITE(numout,*) '   Namelist : namtra_ldf --- lateral mixing parameters (type, direction, coefficients)' 
    145147         WRITE(numout,*) '      type :' 
    146148         WRITE(numout,*) '         no explicit diffusion                   ln_traldf_NONE  = ', ln_traldf_NONE 
     
    166168      ! 
    167169      IF( ln_traldf_NONE ) THEN 
    168          IF(lwp) WRITE(numout,*) '   No diffusive operator selected. ahtu and ahtv are not allocated' 
     170         IF(lwp) WRITE(numout,*) '   ==>>>   No diffusive operator selected. ahtu and ahtv are not allocated' 
    169171         l_ldftra_time = .FALSE. 
    170172         RETURN 
     
    196198         ! 
    197199         CASE(   0  )      !==  constant  ==! 
    198             IF(lwp) WRITE(numout,*) '          tracer mixing coef. = constant = ', rn_aht_0 
     200            IF(lwp) WRITE(numout,*) '   ==>>>   tracer mixing coef. = constant = ', rn_aht_0 
    199201            ahtu(:,:,:) = zah0 * umask(:,:,:) 
    200202            ahtv(:,:,:) = zah0 * vmask(:,:,:) 
    201203            ! 
    202204         CASE(  10  )      !==  fixed profile  ==! 
    203             IF(lwp) WRITE(numout,*) '          tracer mixing coef. = F( depth )' 
     205            IF(lwp) WRITE(numout,*) '   ==>>>   tracer mixing coef. = F( depth )' 
    204206            ahtu(:,:,1) = zah0 * umask(:,:,1)                      ! constant surface value 
    205207            ahtv(:,:,1) = zah0 * vmask(:,:,1) 
     
    207209            ! 
    208210         CASE ( -20 )      !== fixed horizontal shape read in file  ==! 
    209             IF(lwp) WRITE(numout,*) '          tracer mixing coef. = F(i,j) read in eddy_diffusivity.nc file' 
     211            IF(lwp) WRITE(numout,*) '   ==>>>   tracer mixing coef. = F(i,j) read in eddy_diffusivity.nc file' 
    210212            CALL iom_open( 'eddy_diffusivity_2D.nc', inum ) 
    211213            CALL iom_get ( inum, jpdom_data, 'ahtu_2D', ahtu(:,:,1) ) 
     
    218220            ! 
    219221         CASE(  20  )      !== fixed horizontal shape  ==! 
    220             IF(lwp) WRITE(numout,*) '          tracer mixing coef. = F( e1, e2 ) or F( e1^3, e2^3 ) (lap or blp case)' 
     222            IF(lwp) WRITE(numout,*) '   ==>>>   tracer mixing coef. = F( e1, e2 ) or F( e1^3, e2^3 ) (lap or blp case)' 
    221223            IF( ln_traldf_lap )   CALL ldf_c2d( 'TRA', 'LAP', zah0, ahtu, ahtv )    ! surface value proportional to scale factor 
    222224            IF( ln_traldf_blp )   CALL ldf_c2d( 'TRA', 'BLP', zah0, ahtu, ahtv )    ! surface value proportional to scale factor 
    223225            ! 
    224226         CASE(  21  )      !==  time varying 2D field  ==! 
    225             IF(lwp) WRITE(numout,*) '          tracer mixing coef. = F( latitude, longitude, time )' 
    226             IF(lwp) WRITE(numout,*) '                              = F( growth rate of baroclinic instability )' 
    227             IF(lwp) WRITE(numout,*) '                              min value = 0.1 * rn_aht_0' 
    228             IF(lwp) WRITE(numout,*) '                              max value = rn_aht_0 (rn_aeiv_0 if nn_aei_ijk_t=21)' 
    229             IF(lwp) WRITE(numout,*) '                              increased to rn_aht_0 within 20N-20S' 
     227            IF(lwp) WRITE(numout,*) '   ==>>>   tracer mixing coef. = F( latitude, longitude, time )' 
     228            IF(lwp) WRITE(numout,*) '                               = F( growth rate of baroclinic instability )' 
     229            IF(lwp) WRITE(numout,*) '                               min value = 0.1 * rn_aht_0' 
     230            IF(lwp) WRITE(numout,*) '                               max value = rn_aht_0 (rn_aeiv_0 if nn_aei_ijk_t=21)' 
     231            IF(lwp) WRITE(numout,*) '                               increased to rn_aht_0 within 20N-20S' 
    230232            ! 
    231233            l_ldftra_time = .TRUE.     ! will be calculated by call to ldf_tra routine in step.F90 
     
    236238            ! 
    237239         CASE( -30  )      !== fixed 3D shape read in file  ==! 
    238             IF(lwp) WRITE(numout,*) '          tracer mixing coef. = F(i,j,k) read in eddy_diffusivity.nc file' 
     240            IF(lwp) WRITE(numout,*) '   ==>>>   tracer mixing coef. = F(i,j,k) read in eddy_diffusivity.nc file' 
    239241            CALL iom_open( 'eddy_diffusivity_3D.nc', inum ) 
    240242            CALL iom_get ( inum, jpdom_data, 'ahtu_3D', ahtu ) 
     
    247249            ! 
    248250         CASE(  30  )      !==  fixed 3D shape  ==! 
    249             IF(lwp) WRITE(numout,*) '          tracer mixing coef. = F( latitude, longitude, depth )' 
     251            IF(lwp) WRITE(numout,*) '   ==>>>   tracer mixing coef. = F( latitude, longitude, depth )' 
    250252            IF( ln_traldf_lap )   CALL ldf_c2d( 'TRA', 'LAP', zah0, ahtu, ahtv )    ! surface value proportional to scale factor 
    251253            IF( ln_traldf_blp )   CALL ldf_c2d( 'TRA', 'BLP', zah0, ahtu, ahtv )    ! surface value proportional to scale factor 
     
    254256            ! 
    255257         CASE(  31  )      !==  time varying 3D field  ==! 
    256             IF(lwp) WRITE(numout,*) '          tracer mixing coef. = F( latitude, longitude, depth , time )' 
    257             IF(lwp) WRITE(numout,*) '                                proportional to the velocity : |u|e/12 or |u|e^3/12' 
     258            IF(lwp) WRITE(numout,*) '   ==>>>   tracer mixing coef. = F( latitude, longitude, depth , time )' 
     259            IF(lwp) WRITE(numout,*) '                                 proportional to the velocity : |u|e/12 or |u|e^3/12' 
    258260            ! 
    259261            l_ldftra_time = .TRUE.     ! will be calculated by call to ldf_tra routine in step.F90 
     
    382384      !!---------------------------------------------------------------------- 
    383385      ! 
     386      IF(lwp) THEN                      ! control print 
     387         WRITE(numout,*) 
     388         WRITE(numout,*) 'ldf_eiv_init : eddy induced velocity parametrization' 
     389         WRITE(numout,*) '~~~~~~~~~~~~ ' 
     390      ENDIF 
     391      ! 
    384392      REWIND( numnam_ref )              ! Namelist namtra_ldfeiv in reference namelist : eddy induced velocity param. 
    385393      READ  ( numnam_ref, namtra_ldfeiv, IOSTAT = ios, ERR = 901) 
     
    392400 
    393401      IF(lwp) THEN                      ! control print 
    394          WRITE(numout,*) 
    395          WRITE(numout,*) 'ldf_eiv_init : eddy induced velocity parametrization' 
    396          WRITE(numout,*) '~~~~~~~~~~~~ ' 
    397402         WRITE(numout,*) '   Namelist namtra_ldfeiv : ' 
    398403         WRITE(numout,*) '      Eddy Induced Velocity (eiv) param.      ln_ldfeiv     = ', ln_ldfeiv 
     
    415420         ! 
    416421         CASE(   0  )      !==  constant  ==! 
    417             IF(lwp) WRITE(numout,*) '          eddy induced velocity coef. = constant = ', rn_aeiv_0 
     422            IF(lwp) WRITE(numout,*) '   ==>>>   eddy induced velocity coef. = constant = ', rn_aeiv_0 
    418423            aeiu(:,:,:) = rn_aeiv_0 
    419424            aeiv(:,:,:) = rn_aeiv_0 
    420425            ! 
    421426         CASE(  10  )      !==  fixed profile  ==! 
    422             IF(lwp) WRITE(numout,*) '          eddy induced velocity coef. = F( depth )' 
     427            IF(lwp) WRITE(numout,*) '   ==>>>   eddy induced velocity coef. = F( depth )' 
    423428            aeiu(:,:,1) = rn_aeiv_0                                ! constant surface value 
    424429            aeiv(:,:,1) = rn_aeiv_0 
     
    426431            ! 
    427432         CASE ( -20 )      !== fixed horizontal shape read in file  ==! 
    428             IF(lwp) WRITE(numout,*) '          tracer mixing coef. = F(i,j) read in eddy_diffusivity_2D.nc file' 
     433            IF(lwp) WRITE(numout,*) '   ==>>>   tracer mixing coef. = F(i,j) read in eddy_diffusivity_2D.nc file' 
    429434            CALL iom_open ( 'eddy_induced_velocity_2D.nc', inum ) 
    430435            CALL iom_get  ( inum, jpdom_data, 'aeiu', aeiu(:,:,1) ) 
     
    437442            ! 
    438443         CASE(  20  )      !== fixed horizontal shape  ==! 
    439             IF(lwp) WRITE(numout,*) '          tracer mixing coef. = F( e1, e2 ) or F( e1^3, e2^3 ) (lap or bilap case)' 
     444            IF(lwp) WRITE(numout,*) '   ==>>>   tracer mixing coef. = F( e1, e2 ) or F( e1^3, e2^3 ) (lap or bilap case)' 
    440445            CALL ldf_c2d( 'TRA', 'LAP', rn_aeiv_0, aeiu, aeiv )    ! surface value proportional to scale factor 
    441446            ! 
    442447         CASE(  21  )       !==  time varying 2D field  ==! 
    443             IF(lwp) WRITE(numout,*) '          tracer mixing coef. = F( latitude, longitude, time )' 
    444             IF(lwp) WRITE(numout,*) '                              = F( growth rate of baroclinic instability )' 
     448            IF(lwp) WRITE(numout,*) '   ==>>>   tracer mixing coef. = F( latitude, longitude, time )' 
     449            IF(lwp) WRITE(numout,*) '                               = F( growth rate of baroclinic instability )' 
    445450            ! 
    446451            l_ldfeiv_time = .TRUE.     ! will be calculated by call to ldf_tra routine in step.F90 
    447452            ! 
    448453         CASE( -30  )      !== fixed 3D shape read in file  ==! 
    449             IF(lwp) WRITE(numout,*) '          tracer mixing coef. = F(i,j,k) read in eddy_diffusivity_3D.nc file' 
     454            IF(lwp) WRITE(numout,*) '   ==>>>   tracer mixing coef. = F(i,j,k) read in eddy_diffusivity_3D.nc file' 
    450455            CALL iom_open ( 'eddy_induced_velocity_3D.nc', inum ) 
    451456            CALL iom_get  ( inum, jpdom_data, 'aeiu', aeiu ) 
     
    454459            ! 
    455460         CASE(  30  )       !==  fixed 3D shape  ==! 
    456             IF(lwp) WRITE(numout,*) '          tracer mixing coef. = F( latitude, longitude, depth )' 
     461            IF(lwp) WRITE(numout,*) '   ==>>>   tracer mixing coef. = F( latitude, longitude, depth )' 
    457462            CALL ldf_c2d( 'TRA', 'LAP', rn_aeiv_0, aeiu, aeiv )    ! surface value proportional to scale factor 
    458463            !                                                 ! reduction with depth 
     
    464469         ! 
    465470      ELSE 
    466           IF(lwp) WRITE(numout,*) '   eddy induced velocity param is NOT used neither diagnosed' 
     471          IF(lwp) WRITE(numout,*) '   ==>>>   eddy induced velocity param is NOT used neither diagnosed' 
    467472          ln_ldfeiv_dia = .FALSE. 
    468473      ENDIF 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/SBC/sbcmod.F90

    r9168 r9169  
    155155         WRITE(numout,*) '               Stokes drift corr. to vert. velocity ln_sdw        = ', ln_sdw 
    156156         WRITE(numout,*) '                  vertical parametrization          nn_sdrift     = ', nn_sdrift 
    157          WRITE(numout,*) '               wave modified ocean stress           ln_tauwoc      = ', ln_tauwoc 
     157         WRITE(numout,*) '               wave modified ocean stress           ln_tauwoc     = ', ln_tauwoc 
    158158         WRITE(numout,*) '               wave modified ocean stress component ln_tauw       = ', ln_tauw 
    159159         WRITE(numout,*) '               Stokes coriolis term                 ln_stcor      = ', ln_stcor 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/SBC/sbcrnf.F90

    r9168 r9169  
    241241      REAL(wp), DIMENSION(:,:,:), ALLOCATABLE :: zrnfcl     
    242242      REAL(wp), DIMENSION(:,:  ), ALLOCATABLE :: zrnf 
    243       ! 
     243      !! 
    244244      NAMELIST/namsbc_rnf/ cn_dir            , ln_rnf_depth, ln_rnf_tem, ln_rnf_sal,   & 
    245245         &                 sn_rnf, sn_cnf    , sn_s_rnf    , sn_t_rnf  , sn_dep_rnf,   & 
     
    292292         ALLOCATE( sf_rnf(1), STAT=ierror )         ! Create sf_rnf structure (runoff inflow) 
    293293         IF(lwp) WRITE(numout,*) 
    294          IF(lwp) WRITE(numout,*) '          runoffs inflow read in a file' 
     294         IF(lwp) WRITE(numout,*) '   ==>>>   runoffs inflow read in a file' 
    295295         IF( ierror > 0 ) THEN 
    296296            CALL ctl_stop( 'sbc_rnf_init: unable to allocate sf_rnf structure' )   ;   RETURN 
     
    303303      IF( ln_rnf_tem ) THEN                      ! Create (if required) sf_t_rnf structure 
    304304         IF(lwp) WRITE(numout,*) 
    305          IF(lwp) WRITE(numout,*) '          runoffs temperatures read in a file' 
     305         IF(lwp) WRITE(numout,*) '   ==>>>   runoffs temperatures read in a file' 
    306306         ALLOCATE( sf_t_rnf(1), STAT=ierror  ) 
    307307         IF( ierror > 0 ) THEN 
     
    315315      IF( ln_rnf_sal  ) THEN                     ! Create (if required) sf_s_rnf and sf_t_rnf structures 
    316316         IF(lwp) WRITE(numout,*) 
    317          IF(lwp) WRITE(numout,*) '          runoffs salinities read in a file' 
     317         IF(lwp) WRITE(numout,*) '   ==>>>   runoffs salinities read in a file' 
    318318         ALLOCATE( sf_s_rnf(1), STAT=ierror  ) 
    319319         IF( ierror > 0 ) THEN 
     
    327327      IF( ln_rnf_depth ) THEN                    ! depth of runoffs set from a file 
    328328         IF(lwp) WRITE(numout,*) 
    329          IF(lwp) WRITE(numout,*) '          runoffs depth read in a file' 
     329         IF(lwp) WRITE(numout,*) '   ==>>>   runoffs depth read in a file' 
    330330         rn_dep_file = TRIM( cn_dir )//TRIM( sn_dep_rnf%clname ) 
    331331         IF( .NOT. sn_dep_rnf%ln_clim ) THEN   ;   WRITE(rn_dep_file, '(a,"_y",i4)' ) TRIM( rn_dep_file ), nyear    ! add year  
     
    364364         ! 
    365365         IF(lwp) WRITE(numout,*) 
    366          IF(lwp) WRITE(numout,*) '    depth of runoff computed once from max value of runoff' 
    367          IF(lwp) WRITE(numout,*) '    max value of the runoff climatologie (over global domain) rn_rnf_max = ', rn_rnf_max 
    368          IF(lwp) WRITE(numout,*) '    depth over which runoffs is spread                        rn_dep_max = ', rn_dep_max 
    369          IF(lwp) WRITE(numout,*) '     create (=1) a runoff depth file or not (=0)      nn_rnf_depth_file  = ', nn_rnf_depth_file 
     366         IF(lwp) WRITE(numout,*) '   ==>>>  depth of runoff computed once from max value of runoff' 
     367         IF(lwp) WRITE(numout,*) '        max value of the runoff climatologie (over global domain) rn_rnf_max = ', rn_rnf_max 
     368         IF(lwp) WRITE(numout,*) '        depth over which runoffs is spread                        rn_dep_max = ', rn_dep_max 
     369         IF(lwp) WRITE(numout,*) '        create (=1) a runoff depth file or not (=0)      nn_rnf_depth_file  = ', nn_rnf_depth_file 
    370370 
    371371         CALL iom_open( TRIM( sn_rnf%clname ), inum )    !  open runoff file 
     
    420420         ! 
    421421         IF( nn_rnf_depth_file == 1 ) THEN      !  save  output nb levels for runoff 
    422             IF(lwp) WRITE(numout,*) '              create runoff depht file' 
     422            IF(lwp) WRITE(numout,*) '   ==>>>   create runoff depht file' 
    423423            CALL iom_open  ( TRIM( sn_dep_rnf%clname ), inum, ldwrt = .TRUE., kiolib = jprstlib ) 
    424424            CALL iom_rstput( 0, 0, inum, 'rodepth', h_rnf ) 
     
    453453         ENDIF 
    454454         IF(lwp) WRITE(numout,*) 
    455          IF(lwp) WRITE(numout,*) '          Specific treatment used in vicinity of river mouths :' 
     455         IF(lwp) WRITE(numout,*) '   ==>>>   Specific treatment used in vicinity of river mouths :' 
    456456         IF(lwp) WRITE(numout,*) '             - Increase Kz in surface layers (if rn_hrnf > 0 )' 
    457457         IF(lwp) WRITE(numout,*) '               by ', rn_avt_rnf,' m2/s  over ', nkrnf, ' w-levels' 
     
    463463      ELSE                                      ! No treatment at river mouths 
    464464         IF(lwp) WRITE(numout,*) 
    465          IF(lwp) WRITE(numout,*) '          No specific treatment at river mouths' 
     465         IF(lwp) WRITE(numout,*) '   ==>>>   No specific treatment at river mouths' 
    466466         rnfmsk  (:,:) = 0._wp 
    467467         rnfmsk_z(:)   = 0._wp 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/SBC/sbcssr.F90

    r9168 r9169  
    158158      !!---------------------------------------------------------------------- 
    159159      ! 
    160   
     160      IF(lwp) THEN 
     161         WRITE(numout,*) 
     162         WRITE(numout,*) 'sbc_ssr : SST and/or SSS damping term ' 
     163         WRITE(numout,*) '~~~~~~~ ' 
     164      ENDIF 
     165      !  
    161166      REWIND( numnam_ref )              ! Namelist namsbc_ssr in reference namelist :  
    162167      READ  ( numnam_ref, namsbc_ssr, IOSTAT = ios, ERR = 901) 
     
    169174 
    170175      IF(lwp) THEN                 !* control print 
    171          WRITE(numout,*) 
    172          WRITE(numout,*) 'sbc_ssr : SST and/or SSS damping term ' 
    173          WRITE(numout,*) '~~~~~~~ ' 
    174176         WRITE(numout,*) '   Namelist namsbc_ssr :' 
    175177         WRITE(numout,*) '      SST restoring term (Yes=1)             nn_sstr        = ', nn_sstr 
    176178         WRITE(numout,*) '         dQ/dT (restoring magnitude on SST)     rn_dqdt     = ', rn_dqdt, ' W/m2/K' 
    177          WRITE(numout,*) '      SSS damping term (Yes=1, salt flux)    nn_sssr        = ', nn_sssr 
     179         WRITE(numout,*) '      SSS damping term (Yes=1, salt   flux)  nn_sssr        = ', nn_sssr 
    178180         WRITE(numout,*) '                       (Yes=2, volume flux) ' 
    179181         WRITE(numout,*) '         dE/dS (restoring magnitude on SST)     rn_deds     = ', rn_deds, ' mm/day' 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/TRA/eosbn2.F90

    r9168 r9169  
    12721272      CASE( np_teos10 )                       !==  polynomial TEOS-10  ==! 
    12731273         IF(lwp) WRITE(numout,*) 
    1274          IF(lwp) WRITE(numout,*) '          use of TEOS-10 equation of state (cons. temp. and abs. salinity)' 
     1274         IF(lwp) WRITE(numout,*) '   ==>>>   use of TEOS-10 equation of state (cons. temp. and abs. salinity)' 
    12751275         ! 
    12761276         l_useCT = .TRUE.                          ! model temperature is Conservative temperature  
     
    14641464         ! 
    14651465         IF(lwp) WRITE(numout,*) 
    1466          IF(lwp) WRITE(numout,*) '          use of EOS-80 equation of state (pot. temp. and pract. salinity)' 
     1466         IF(lwp) WRITE(numout,*) '   ==>>>   use of EOS-80 equation of state (pot. temp. and pract. salinity)' 
    14671467         ! 
    14681468         l_useCT = .FALSE.                         ! model temperature is Potential temperature 
     
    16551655         IF(lwp) THEN 
    16561656            WRITE(numout,*) 
    1657             WRITE(numout,*) '          use of simplified eos:    rhd(dT=T-10,dS=S-35,Z) = ' 
    1658             WRITE(numout,*) '             [-a0*(1+lambda1/2*dT+mu1*Z)*dT + b0*(1+lambda2/2*dT+mu2*Z)*dS - nu*dT*dS]/rau0' 
    1659             WRITE(numout,*) 
    1660             WRITE(numout,*) '             thermal exp. coef.    rn_a0      = ', rn_a0 
    1661             WRITE(numout,*) '             saline  cont. coef.   rn_b0      = ', rn_b0 
    1662             WRITE(numout,*) '             cabbeling coef.       rn_lambda1 = ', rn_lambda1 
    1663             WRITE(numout,*) '             cabbeling coef.       rn_lambda2 = ', rn_lambda2 
    1664             WRITE(numout,*) '             thermobar. coef.      rn_mu1     = ', rn_mu1 
    1665             WRITE(numout,*) '             thermobar. coef.      rn_mu2     = ', rn_mu2 
    1666             WRITE(numout,*) '             2nd cabbel. coef.     rn_nu      = ', rn_nu 
    1667             WRITE(numout,*) '               Caution: rn_beta0=0 incompatible with ddm parameterization ' 
     1657            WRITE(numout,*) '   ==>>>   use of simplified eos:    ' 
     1658            WRITE(numout,*) '              rhd(dT=T-10,dS=S-35,Z) = [-a0*(1+lambda1/2*dT+mu1*Z)*dT ' 
     1659            WRITE(numout,*) '                                       + b0*(1+lambda2/2*dT+mu2*Z)*dS - nu*dT*dS] / rau0' 
     1660            WRITE(numout,*) '              with the following coefficients :' 
     1661            WRITE(numout,*) '                 thermal exp. coef.    rn_a0      = ', rn_a0 
     1662            WRITE(numout,*) '                 saline  cont. coef.   rn_b0      = ', rn_b0 
     1663            WRITE(numout,*) '                 cabbeling coef.       rn_lambda1 = ', rn_lambda1 
     1664            WRITE(numout,*) '                 cabbeling coef.       rn_lambda2 = ', rn_lambda2 
     1665            WRITE(numout,*) '                 thermobar. coef.      rn_mu1     = ', rn_mu1 
     1666            WRITE(numout,*) '                 thermobar. coef.      rn_mu2     = ', rn_mu2 
     1667            WRITE(numout,*) '                 2nd cabbel. coef.     rn_nu      = ', rn_nu 
     1668            WRITE(numout,*) '              Caution: rn_beta0=0 incompatible with ddm parameterization ' 
    16681669         ENDIF 
    16691670         l_useCT = .TRUE.          ! Use conservative temperature 
     
    16821683      IF(lwp) THEN 
    16831684         IF( l_useCT )   THEN 
    1684             WRITE(numout,*) '             model uses Conservative Temperature' 
    1685             WRITE(numout,*) '             Important: model must be initialized with CT and SA fields' 
     1685            WRITE(numout,*) 
     1686            WRITE(numout,*) '   ==>>>   model uses Conservative Temperature' 
     1687            WRITE(numout,*) '           Important: model must be initialized with CT and SA fields' 
    16861688         ELSE 
    1687             WRITE(numout,*) '             model does not use Conservative Temperature' 
     1689            WRITE(numout,*) 
     1690            WRITE(numout,*) '   ==>>>   model does not use Conservative Temperature' 
    16881691         ENDIF 
    16891692      ENDIF 
    16901693      ! 
    16911694      IF(lwp) WRITE(numout,*) 
    1692       IF(lwp) WRITE(numout,*) '          volumic mass of reference           rau0  = ', rau0   , ' kg/m^3' 
    1693       IF(lwp) WRITE(numout,*) '          1. / rau0                        r1_rau0  = ', r1_rau0, ' m^3/kg' 
    1694       IF(lwp) WRITE(numout,*) '          ocean specific heat                 rcp   = ', rcp    , ' J/Kelvin' 
    1695       IF(lwp) WRITE(numout,*) '          rau0 * rcp                       rau0_rcp = ', rau0_rcp 
    1696       IF(lwp) WRITE(numout,*) '          1. / ( rau0 * rcp )           r1_rau0_rcp = ', r1_rau0_rcp 
     1695      IF(lwp) WRITE(numout,*) '   Associated physical constant' 
     1696      IF(lwp) WRITE(numout,*) '      volumic mass of reference           rau0  = ', rau0   , ' kg/m^3' 
     1697      IF(lwp) WRITE(numout,*) '      1. / rau0                        r1_rau0  = ', r1_rau0, ' m^3/kg' 
     1698      IF(lwp) WRITE(numout,*) '      ocean specific heat                 rcp   = ', rcp    , ' J/Kelvin' 
     1699      IF(lwp) WRITE(numout,*) '      rau0 * rcp                       rau0_rcp = ', rau0_rcp 
     1700      IF(lwp) WRITE(numout,*) '      1. / ( rau0 * rcp )           r1_rau0_rcp = ', r1_rau0_rcp 
    16971701      ! 
    16981702   END SUBROUTINE eos_init 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/TRA/traqsr.F90

    r9168 r9169  
    379379      CASE( np_RGB , np_RGBc )         !==  Red-Green-Blue light penetration  ==! 
    380380         !                              
    381          IF(lwp)   WRITE(numout,*) '   R-G-B   light penetration ' 
     381         IF(lwp)   WRITE(numout,*) '   ==>>>   R-G-B   light penetration ' 
    382382         ! 
    383383         CALL trc_oce_rgb( rkrgb )                 ! tabulated attenuation coef. 
     
    388388         ! 
    389389         IF( nqsr == np_RGBc ) THEN                ! Chl data : set sf_chl structure 
    390             IF(lwp) WRITE(numout,*) '        Chlorophyll read in a file' 
     390            IF(lwp) WRITE(numout,*) '   ==>>>   Chlorophyll read in a file' 
    391391            ALLOCATE( sf_chl(1), STAT=ierror ) 
    392392            IF( ierror > 0 ) THEN 
     
    400400         ENDIF 
    401401         IF( nqsr == np_RGB ) THEN                 ! constant Chl 
    402             IF(lwp) WRITE(numout,*) '        Constant Chlorophyll concentration = 0.05' 
     402            IF(lwp) WRITE(numout,*) '   ==>>>   Constant Chlorophyll concentration = 0.05' 
    403403         ENDIF 
    404404         ! 
    405405      CASE( np_2BD )                   !==  2 bands light penetration  ==! 
    406406         ! 
    407          IF(lwp)  WRITE(numout,*) '   2 bands light penetration' 
     407         IF(lwp)  WRITE(numout,*) '   ==>>>   2 bands light penetration' 
    408408         ! 
    409409         nksr = trc_oce_ext_lev( rn_si1, 100._wp )    ! level of light extinction 
     
    412412      CASE( np_BIO )                   !==  BIO light penetration  ==! 
    413413         ! 
    414          IF(lwp) WRITE(numout,*) '   bio-model light penetration' 
     414         IF(lwp) WRITE(numout,*) '   ==>>>   bio-model light penetration' 
    415415         IF( .NOT.lk_top )   CALL ctl_stop( 'No bio model : ln_qsr_bio = true impossible ' ) 
    416416         ! 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/USR/usrdef_nam.F90

    r9124 r9169  
    104104      kperio = 0                    ! GYRE configuration : closed domain 
    105105      ! 
    106       WRITE(ldtxt(ii),*) '   '                                                                        ;   ii = ii + 1 
    107       WRITE(ldtxt(ii),*) '   Lateral b.c. of the global domain set to closed     jperio = ', kperio   ;   ii = ii + 1 
     106      WRITE(ldtxt(ii),*) '   '                                                                            ;   ii = ii + 1 
     107      WRITE(ldtxt(ii),*) '   Lateral b.c. of the global domain set to closed     jperio = ', kperio       ;   ii = ii + 1 
    108108      ! 
    109109   END SUBROUTINE usr_def_nam 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/ZDF/zdfphy.F90

    r9108 r9169  
    8383      !!---------------------------------------------------------------------- 
    8484      ! 
     85      IF(lwp) THEN 
     86         WRITE(numout,*) 
     87         WRITE(numout,*) 'zdf_phy_init: ocean vertical physics' 
     88         WRITE(numout,*) '~~~~~~~~~~~~' 
     89      ENDIF 
     90      ! 
    8591      !                           !==  Namelist  ==! 
    8692      REWIND( numnam_ref )              ! Namelist namzdf in reference namelist : Vertical mixing parameters 
     
    94100      ! 
    95101      IF(lwp) THEN                      ! Parameter print 
    96          WRITE(numout,*) 
    97          WRITE(numout,*) 'zdf_phy_init: vertical physics' 
    98          WRITE(numout,*) '~~~~~~~~~~~~' 
    99102         WRITE(numout,*) '   Namelist namzdf : set vertical mixing mixing parameters' 
    100103         WRITE(numout,*) '      vertical closure scheme' 
     
    163166      IF(lwp) THEN 
    164167         WRITE(numout,*) 
    165          IF    ( ln_zdfnpc ) THEN  ;   WRITE(numout,*) '      convection: use non penetrative convective scheme' 
    166          ELSEIF( ln_zdfevd ) THEN  ;   WRITE(numout,*) '      convection: use enhanced vertical diffusion scheme' 
    167          ELSE                      ;   WRITE(numout,*) '      convection: no specific scheme used' 
     168         IF    ( ln_zdfnpc ) THEN  ;   WRITE(numout,*) '   ==>>>   convection: use non penetrative convective scheme' 
     169         ELSEIF( ln_zdfevd ) THEN  ;   WRITE(numout,*) '   ==>>>   convection: use enhanced vertical diffusion scheme' 
     170         ELSE                      ;   WRITE(numout,*) '   ==>>>   convection: no specific scheme used' 
    168171         ENDIF 
    169172      ENDIF 
     
    171174      IF(lwp) THEN               !==  Double Diffusion Mixing parameterization  ==!   (ddm) 
    172175         WRITE(numout,*) 
    173          IF( ln_zdfddm ) THEN   ;   WRITE(numout,*) '      use double diffusive mixing: avs /= avt' 
    174          ELSE                   ;   WRITE(numout,*) '      No  double diffusive mixing: avs = avt' 
     176         IF( ln_zdfddm ) THEN   ;   WRITE(numout,*) '   ==>>>   use double diffusive mixing: avs /= avt' 
     177         ELSE                   ;   WRITE(numout,*) '   ==>>>   No  double diffusive mixing: avs = avt' 
    175178         ENDIF 
    176179      ENDIF 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/ZDF/zdftke.F90

    r9104 r9169  
    678678         WRITE(numout,*) '          type of tke penetration profile            nn_htau   = ', nn_htau 
    679679         WRITE(numout,*) '          fraction of TKE that penetrates            rn_efr    = ', rn_efr 
    680          WRITE(numout,*) 
    681680         IF( ln_drg ) THEN 
     681            WRITE(numout,*) 
    682682            WRITE(numout,*) '   Namelist namdrg_top/_bot:   used values:' 
    683683            WRITE(numout,*) '      top    ocean cavity roughness (m)          rn_z0(_top)= ', r_z0_top 
     
    685685         ENDIF 
    686686         WRITE(numout,*) 
    687          WRITE(numout,*) 
    688          WRITE(numout,*) '   ==>> critical Richardson nb with your parameters  ri_cri = ', ri_cri 
     687         WRITE(numout,*) '   ==>>   critical Richardson nb with your parameters  ri_cri = ', ri_cri 
    689688         WRITE(numout,*) 
    690689      ENDIF 
     
    693692         rn_emin  = 1.e-10_wp             ! specific values of rn_emin & rmxl_min are used 
    694693         rmxl_min = 1.e-03_wp             ! associated avt minimum = molecular salt diffusivity (10^-9 m2/s) 
    695          IF(lwp) WRITE(numout,*) '      Internal wave-driven mixing case:   force   rn_emin = 1.e-10 and rmxl_min = 1.e-3 ' 
     694         IF(lwp) WRITE(numout,*) '   ==>>   Internal wave-driven mixing case:   force   rn_emin = 1.e-10 and rmxl_min = 1.e-3' 
    696695      ELSE                          ! standard case : associated avt minimum = molecular viscosity (10^-6 m2/s) 
    697696         rmxl_min = 1.e-6_wp / ( rn_ediff * SQRT( rn_emin ) )    ! resulting minimum length to recover molecular viscosity 
    698          IF(lwp) WRITE(numout,*) '      minimum mixing length with your parameters rmxl_min = ', rmxl_min 
     697         IF(lwp) WRITE(numout,*) '   ==>>   minimum mixing length with your parameters rmxl_min = ', rmxl_min 
    699698      ENDIF 
    700699      ! 
     
    709708      ! 
    710709      IF( ln_mxl0 ) THEN 
    711          IF(lwp) WRITE(numout,*) '   use a surface mixing length = F(stress) :   set rn_mxl0 = rmxl_min' 
     710         IF(lwp) WRITE(numout,*) 
     711         IF(lwp) WRITE(numout,*) '   ==>>   use a surface mixing length = F(stress) :   set rn_mxl0 = rmxl_min' 
    712712         rn_mxl0 = rmxl_min 
    713713      ENDIF 
     
    763763               CALL iom_get( numror, jpdom_autoglo, 'dissl', dissl ) 
    764764            ELSE                                          ! start TKE from rest 
     765               IF(lwp) WRITE(numout,*) 
    765766               IF(lwp) WRITE(numout,*) '   ==>>   previous run without TKE scheme, set en to background values' 
    766767               en   (:,:,:) = rn_emin * wmask(:,:,:) 
     
    769770            ENDIF 
    770771         ELSE                                   !* Start from rest 
     772            IF(lwp) WRITE(numout,*) 
    771773            IF(lwp) WRITE(numout,*) '   ==>>   start from rest: set en to the background value' 
    772774            en   (:,:,:) = rn_emin * wmask(:,:,:) 
     
    777779      ELSEIF( TRIM(cdrw) == 'WRITE' ) THEN   ! Create restart file 
    778780         !                                   ! ------------------- 
    779          IF(lwp) WRITE(numout,*) '---- tke-rst ----' 
     781         IF(lwp) WRITE(numout,*) '---- tke_rst ----' 
    780782         CALL iom_rstput( kt, nitrst, numrow, 'en'   , en    ) 
    781783         CALL iom_rstput( kt, nitrst, numrow, 'avt_k', avt_k ) 
  • branches/2017/dev_merge_2017/NEMOGCM/NEMO/OPA_SRC/nemogcm.F90

    r9168 r9169  
    395395         WRITE(numout,*) '                       NEMO team' 
    396396         WRITE(numout,*) '            Ocean General Circulation Model' 
    397          WRITE(numout,*) '                NEMO version 3.7  (2016) ' 
     397         WRITE(numout,*) '                NEMO version 4.0  (2017) ' 
    398398         WRITE(numout,*) 
    399399         WRITE(numout,*) 
Note: See TracChangeset for help on using the changeset viewer.