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 389 for trunk/NEMO/OPA_SRC/SBC – NEMO

Changeset 389 for trunk/NEMO/OPA_SRC/SBC


Ignore:
Timestamp:
2006-03-09T18:22:04+01:00 (18 years ago)
Author:
opalod
Message:

RB:nemo_v1_update_038: first integration of Agrif :

  • configuration parameters are just integer when agrif is used
  • add call to agrif routines with key_agrif
Location:
trunk/NEMO/OPA_SRC/SBC
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMO/OPA_SRC/SBC/flx_bulk_daily.h90

    r247 r389  
    7979      REAL(wp), DIMENSION(jpk) ::   zlev           ! ??? 
    8080      CHARACTER(len=45)  ::  & 
    81          clname_n = 'tair_1d.nc',        & 
    82          clname_c = 'hum_cloud_1m.nc',   & 
    83          clname_x = 'rain_1m.nc',        & 
     81         clname_n ,        & 
     82         clname_c ,   & 
     83         clname_x ,        & 
     84         clname_w  
     85      !!--------------------------------------------------------------------- 
     86         clname_n = 'tair_1d.nc' 
     87         clname_c = 'hum_cloud_1m.nc' 
     88         clname_x = 'rain_1m.nc' 
    8489         clname_w = 'wspd_1d.nc' 
    8590      !!--------------------------------------------------------------------- 
  • trunk/NEMO/OPA_SRC/SBC/flx_bulk_monthly.h90

    r319 r389  
    9595         zlon   , zlat                 ! ??? 
    9696      CHARACTER (len=32) ::   & 
    97          clname = 'flx.nc'             ! flux filename 
     97         clname            ! flux filename 
    9898      !!--------------------------------------------------------------------- 
     99         clname = 'flx.nc' 
    99100 
    100101 
     
    131132 
    132133         ! title, dimensions and tests 
     134#if defined key_AGRIF 
     135      if ( .NOT. Agrif_Root() ) then 
     136         clname = TRIM(Agrif_CFixed())//'_'//TRIM(clname) 
     137      endif 
     138#endif     
    133139         CALL flinopen( clname, mig(1), nlci, mjg(1), nlcj,   & 
    134140            &          .FALSE., ipi, ipj, ipk, zlon, zlat, zlev,   & 
     
    202208               WRITE(numout,*) 
    203209               WRITE(numout,*) 'Clio mounth: ',nflx1,'  field: ',jm,' multiply by ',0.1 
    204                CALL prihre(flxdta(1,1,1,jm),jpi,jpj,1,jpi,20,1,jpj,10,.1,numout) 
     210               CALL prihre(flxdta(:,:,1,jm),jpi,jpj,1,jpi,20,1,jpj,10,.1,numout) 
    205211            END DO 
    206212         ENDIF 
     
    269275               WRITE(numout,*) 'jpf =  ', jpf !C a u t i o n : information need for SX5NEC compilo bug 
    270276               WRITE(numout,*) 'Clio mounth: ',nflx11,'  field: ',jm,' multiply by ',0.1 
    271                CALL prihre(flxdta(1,1,1,jm),jpi,jpj,1,jpi,20,1,jpj,10,.1,numout) 
     277               CALL prihre(flxdta(:,:,1,jm),jpi,jpj,1,jpi,20,1,jpj,10,.1,numout) 
    272278               WRITE(numout,*) 
    273279            END DO 
  • trunk/NEMO/OPA_SRC/SBC/flx_forced_daily.h90

    r247 r389  
    118118         ! Close/open file if new year  
    119119 
    120          IF( nyearflx /= 0 )   CALL flinclo(numflx) 
     120         IF( nyearflx /= 0 .AND. kt /= nit000 )   CALL flinclo(numflx) 
    121121 
    122122         iy = nyear 
    123123         IF(lwp) WRITE (numout,*) iy 
    124124         WRITE(clname,'("flx_1d.nc")')  
     125#if defined key_AGRIF 
     126      if ( .NOT. Agrif_Root() ) then 
     127         clname = TRIM(Agrif_CFixed())//'_'//TRIM(clname) 
     128      endif 
     129#endif          
    125130         IF(lwp) WRITE (numout,*)' open flx file = ',clname 
    126131         CALL FLUSH(numout) 
     
    172177                  WRITE(numout,*) 
    173178                  WRITE(numout,*) ' Q * .1, day: ',ndastp 
    174                   CALL prihre(flxdta(1,1,1),jpi,jpj,1,jpi,20,1,jpj,10,.1,numout) 
     179                  CALL prihre(flxdta(:,:,1),jpi,jpj,1,jpi,20,1,jpj,10,.1,numout) 
    175180                  WRITE(numout,*) 
    176181                  WRITE(numout,*) ' QSR * .1, day: ',ndastp 
    177                   CALL prihre(flxdta(1,1,2),jpi,jpj,1,jpi,20,1,jpj,10,.1,numout) 
     182                  CALL prihre(flxdta(:,:,2),jpi,jpj,1,jpi,20,1,jpj,10,.1,numout) 
    178183                  WRITE(numout,*) 
    179184                  WRITE(numout,*) ' E-P *86400, day: ',ndastp 
    180                   CALL prihre(flxdta(1,1,3),jpi,jpj,1,jpi,20,1,jpj,10,86400.,numout) 
     185                  CALL prihre(flxdta(:,:,3),jpi,jpj,1,jpi,20,1,jpj,10,86400.,numout) 
    181186                  WRITE(numout,*) ' ' 
    182187               ENDIF 
  • trunk/NEMO/OPA_SRC/SBC/flxrnf.F90

    r322 r389  
    104104# endif 
    105105      CHARACTER (len=32) ::   & 
    106          clname = 'runoff_1m_nomask'       ! monthly runoff filename 
     106         clname                            ! monthly runoff filename 
    107107      INTEGER, PARAMETER :: jpmois = 12 
    108108      INTEGER  ::   ipi, ipj, ipk          ! temporary integers 
     
    117117         zcoefr                            ! coeff of advection link to runoff 
    118118      !!---------------------------------------------------------------------- 
     119         clname = 'runoff_1m_nomask'       ! monthly runoff filename 
    119120       
    120121      IF( kt == nit000 ) THEN 
     
    266267         ! when reading the NetCDF file runoff_1m_nomask.nc 
    267268         IF( cp_cfg == 'orca' .AND. jp_cfg == 2 )   THEN 
    268             DO jj = 1, jpj 
    269                DO ji = 1, jpi 
    270                   IF( gphit(ji,jj) > 40 .AND. gphit(ji,jj) < 65 )   runoff(ji,jj) = 0.85 * runoff(ji,jj) 
    271                END DO 
     269         DO jj = 1, jpj 
     270            DO ji = 1, jpi 
     271               IF( gphit(ji,jj) > 40 .AND. gphit(ji,jj) < 65 )   runoff(ji,jj) = 0.85 * runoff(ji,jj) 
    272272            END DO 
     273         END DO 
    273274         ENDIF 
    274275          
  • trunk/NEMO/OPA_SRC/SBC/tau_forced_daily.h90

    r247 r389  
    1414 
    1515   CHARACTER (len=34) ::   &      !!! * monthly climatology/interanual fields 
    16       cl_taux = 'taux.nc',  & ! generic name of the i-component monthly NetCDF file 
    17       cl_tauy = 'tauy.nc'     ! generic name of the j-component monthly NetCDF file 
     16      cl_taux ,  & ! generic name of the i-component monthly NetCDF file 
     17      cl_tauy      ! generic name of the j-component monthly NetCDF file 
    1818   !!---------------------------------------------------------------------- 
    1919   !!   OPA 9.0 , LOCEAN-IPSL (2005)  
     
    6767      REAL(wp) ::   zsecond, zdate0 
    6868      !!--------------------------------------------------------------------- 
     69      cl_taux = 'taux.nc' 
     70      cl_tauy = 'tauy.nc' 
    6971 
    7072      ! -------------- ! 
     
    9193         ENDIF 
    9294         ! title, dimensions and tests 
     95#if defined key_AGRIF 
     96      if ( .NOT. Agrif_Root() ) then 
     97         cl_taux = TRIM(Agrif_CFixed())//'_'//TRIM(cl_taux) 
     98      endif 
     99#endif 
    93100          
    94101         CALL flinopen( cl_taux, mig(1), nlci, mjg(1), nlcj,   &   ! taux on U-grid 
     
    110117            nstop = nstop + 1 
    111118         ENDIF 
     119#if defined key_AGRIF 
     120      if ( .NOT. Agrif_Root() ) then 
     121         cl_tauy = TRIM(Agrif_CFixed())//'_'//TRIM(cl_tauy) 
     122      endif 
     123#endif 
    112124 
    113125         CALL flinopen( cl_tauy, mig(1), nlci, mjg(1), nlcj,   &   ! tauy on V-grid 
  • trunk/NEMO/OPA_SRC/SBC/tau_forced_monthly.h90

    r319 r389  
    1414 
    1515   CHARACTER (len=34) ::   &      !!! * monthly climatology/interanual fields 
    16       cl_taux = 'taux_1m.nc',  & ! generic name of the i-component monthly NetCDF file 
    17       cl_tauy = 'tauy_1m.nc'     ! generic name of the j-component monthly NetCDF file 
     16      cl_taux,  & ! generic name of the i-component monthly NetCDF file 
     17      cl_tauy     ! generic name of the j-component monthly NetCDF file 
    1818 
    1919   REAL(wp), DIMENSION(jpi,jpj,2) ::   & 
     
    7777         zxy          ! coefficient of the linear time interpolation 
    7878      !!--------------------------------------------------------------------- 
     79      cl_taux = 'taux_1m.nc' 
     80      cl_tauy = 'tauy_1m.nc' 
    7981 
    8082      ! -------------- ! 
     
    106108          
    107109         ! title, dimensions and tests 
     110 
     111#if defined key_AGRIF 
     112      if ( .NOT. Agrif_Root() ) then 
     113         cl_taux = TRIM(Agrif_CFixed())//'_'//TRIM(cl_taux) 
     114      endif 
     115#endif 
    108116          
    109117         CALL flinopen( cl_taux, mig(1), nlci, mjg(1), nlcj,   &   ! taux on U-grid 
     
    126134            nstop = nstop + 1 
    127135         ENDIF 
    128  
     136#if defined key_AGRIF 
     137      if ( .NOT. Agrif_Root() ) then 
     138         cl_tauy = TRIM(Agrif_CFixed())//'_'//TRIM(cl_tauy) 
     139      endif 
     140#endif 
    129141         CALL flinopen( cl_tauy, mig(1), nlci, mjg(1), nlcj,   &   ! tauy on V-grid 
    130142                        .FALSE., ipi   , ipj, ipk   ,        & 
     
    185197            WRITE(numout,*) 
    186198            WRITE(numout,*) ' month: ', ntau1, '  taux: 1 multiply by ', 1. 
    187             CALL prihre( taux_dta(1,1,1), jpi, jpj, 1, jpi, 20, 1, jpj, 10, 1., numout ) 
     199            CALL prihre( taux_dta(:,:,1), jpi, jpj, 1, jpi, 20, 1, jpj, 10, 1., numout ) 
    188200            WRITE(numout,*) 
    189201            WRITE(numout,*) ' month: ', ntau2, '  tauy: 2 multiply by ', 1. 
    190             CALL prihre( tauy_dta(1,1,2), jpi, jpj, 1, jpi, 20, 1, jpj, 10, 1., numout ) 
     202            CALL prihre( tauy_dta(:,:,2), jpi, jpj, 1, jpi, 20, 1, jpj, 10, 1., numout ) 
    191203         ENDIF 
    192204 
Note: See TracChangeset for help on using the changeset viewer.