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

Changeset 1786


Ignore:
Timestamp:
2009-12-02T09:50:10+01:00 (14 years ago)
Author:
sga
Message:

add new AGRIF without LIM code to NEMO branch dev_005_AWL taken from NOCS NEMO branch noc_dev_024_AWL revision 1051 (patch file differences from NOCS NEMO trunk revision 1043)

Location:
branches/dev_005_AWL/NEMO
Files:
1 added
3 edited

Legend:

Unmodified
Added
Removed
  • branches/dev_005_AWL/NEMO/NST_SRC/agrif_opa_interp.F90

    r1605 r1786  
    2525   USE phycst 
    2626   USE in_out_manager 
     27#if defined key_agrif_nolim 
     28   USE agrif_nolim 
     29#endif 
    2730 
    2831   IMPLICIT NONE 
     
    3033     
    3134   PUBLIC   Agrif_tra, Agrif_dyn, interpu, interpv 
     35#if defined key_agrif_nolim 
     36   PUBLIC interputau, interpvtau 
     37#endif 
    3238 
    3339#  include "domzgr_substitute.h90"   
     
    607613   END SUBROUTINE interpv2d 
    608614 
     615#if defined key_agrif_nolim 
     616   SUBROUTINE interputau(tabres,i1,i2,j1,j2) 
     617      !!----------------------------------------------------------------------   
     618      !!                  ***  ROUTINE interputau  *** 
     619      !!----------------------------------------------------------------------   
     620#  include "domzgr_substitute.h90"    
     621     
     622      INTEGER, INTENT(in) :: i1,i2,j1,j2 
     623      REAL(wp),DIMENSION(i1:i2,j1:j2), INTENT(inout) :: tabres 
     624 
     625      INTEGER :: ji,jj 
     626 
     627      DO jj=j1,j2 
     628         DO ji=i1,i2 
     629            tabres(ji,jj) = e2u(ji,jj) * utau_nst(ji,jj) 
     630#if ! defined key_zco 
     631            tabres(ji,jj) = tabres(ji,jj) * fse3u(ji,jj,1) 
     632#endif 
     633         END DO 
     634      END DO 
     635   END SUBROUTINE interputau 
     636 
     637   SUBROUTINE interpvtau(tabres,i1,i2,j1,j2) 
     638      !!----------------------------------------------------------------------   
     639      !!                  ***  ROUTINE interpvtau  *** 
     640      !!----------------------------------------------------------------------   
     641#  include "domzgr_substitute.h90"  
     642       
     643      INTEGER, INTENT(in) :: i1,i2,j1,j2 
     644      REAL(wp),DIMENSION(i1:i2,j1:j2), INTENT(inout) :: tabres 
     645 
     646      INTEGER :: ji, jj 
     647 
     648      DO jj=j1,j2 
     649         DO ji=i1,i2 
     650            tabres(ji,jj) = e1v(ji,jj) * vtau_nst(ji,jj) 
     651#if ! defined key_zco 
     652            tabres(ji,jj) = tabres(ji,jj) * fse3v(ji,jj,1) 
     653#endif            
     654         END DO 
     655      END DO 
     656 
     657   END SUBROUTINE interpvtau 
     658#endif 
     659 
    609660#else 
    610661   !!---------------------------------------------------------------------- 
  • branches/dev_005_AWL/NEMO/NST_SRC/agrif_user.F90

    r1605 r1786  
    8888      REAL(wp) :: tabtrtemp(jpi,jpj,jpk,jptra) 
    8989#endif  
     90#if defined key_agrif_nolim 
     91      REAL(wp) :: tabflxtemp(jpi,jpj) 
     92#endif 
    9093      LOGICAL check_namelist 
    9194      !!---------------------------------------------------------------------- 
     
    135138#endif 
    136139       
     140#if defined key_lim2 && defined key_agrif_nolim 
     141      Call Agrif_Set_type(utau_nst,(/1,2/),(/2,3/)) 
     142      Call Agrif_Set_type(vtau_nst,(/2,1/),(/3,2/)) 
     143      Call Agrif_Set_type(taum_nst,(/2,2/),(/3,3/)) 
     144      Call Agrif_Set_type(qsr_nst,(/2,2/),(/3,3/)) 
     145      Call Agrif_Set_type(qns_nst,(/2,2/),(/3,3/)) 
     146      Call Agrif_Set_type(emp_nst,(/2,2/),(/3,3/)) 
     147      Call Agrif_Set_type(emps_nst,(/2,2/),(/3,3/)) 
     148      Call Agrif_Set_type(wndm_nst,(/2,2/),(/3,3/)) 
     149      Call Agrif_Set_type(fri_nst,(/2,2/),(/3,3/)) 
     150      Call Agrif_Set_type(tag_nst,(/2,2/),(/3,3/)) 
     151#endif 
     152 
    137153      ! 2. Space directions for each variables 
    138154      !--------------------------------------- 
     
    164180#endif 
    165181 
     182#if defined key_lim2 && defined key_agrif_nolim 
     183      Call Agrif_Set_raf(utau_nst,(/'x','y'/)) 
     184      Call Agrif_Set_raf(vtau_nst,(/'x','y'/)) 
     185      Call Agrif_Set_raf(taum_nst,(/'x','y'/)) 
     186      Call Agrif_Set_raf(qsr_nst,(/'x','y'/)) 
     187      Call Agrif_Set_raf(qns_nst,(/'x','y'/)) 
     188      Call Agrif_Set_raf(emp_nst,(/'x','y'/)) 
     189      Call Agrif_Set_raf(emps_nst,(/'x','y'/)) 
     190      Call Agrif_Set_raf(wndm_nst,(/'x','y'/)) 
     191      Call Agrif_Set_raf(fri_nst,(/'x','y'/)) 
     192      Call Agrif_Set_raf(tag_nst,(/'x','y'/)) 
     193#endif 
     194 
    166195      ! 3. Type of interpolation 
    167196      !-------------------------  
     
    186215#endif 
    187216 
     217#if defined key_lim2 && defined key_agrif_nolim 
     218      Call Agrif_Set_interp(utau_nst,interp1=Agrif_linear,interp2=AGRIF_ppm) 
     219      Call Agrif_Set_interp(vtau_nst,interp1=AGRIF_ppm,interp2=Agrif_linear) 
     220      Call Agrif_Set_interp(taum_nst,interp=AGRIF_linear) 
     221      Call Agrif_Set_interp(qsr_nst,interp=AGRIF_linear) 
     222      Call Agrif_Set_interp(qns_nst,interp=AGRIF_linear) 
     223      Call Agrif_Set_interp(emp_nst,interp=AGRIF_linear) 
     224      Call Agrif_Set_interp(emps_nst,interp=AGRIF_linear) 
     225      Call Agrif_Set_interp(wndm_nst,interp=AGRIF_linear) 
     226      Call Agrif_Set_interp(fri_nst,interp=AGRIF_linear) 
     227      Call Agrif_Set_interp(tag_nst,interp=AGRIF_linear) 
     228 
     229      Call Agrif_Set_bcinterp(utau_nst,interp1=Agrif_linear,interp2=AGRIF_ppm) 
     230      Call Agrif_Set_bcinterp(vtau_nst,interp1=AGRIF_ppm,interp2=Agrif_linear) 
     231      Call Agrif_Set_bcinterp(taum_nst,interp=AGRIF_linear) 
     232      Call Agrif_Set_bcinterp(qsr_nst,interp=AGRIF_linear) 
     233      Call Agrif_Set_bcinterp(qns_nst,interp=AGRIF_linear) 
     234      Call Agrif_Set_bcinterp(emp_nst,interp=AGRIF_linear) 
     235      Call Agrif_Set_bcinterp(emps_nst,interp=AGRIF_linear) 
     236      Call Agrif_Set_bcinterp(wndm_nst,interp=AGRIF_linear) 
     237      Call Agrif_Set_bcinterp(fri_nst,interp=AGRIF_linear) 
     238      Call Agrif_Set_bcinterp(tag_nst,interp=AGRIF_linear) 
     239#endif 
     240 
    188241      ! 4. Location of interpolation 
    189242      !----------------------------- 
     
    208261#endif 
    209262 
     263#if defined key_lim2 && defined key_agrif_nolim 
     264      Call Agrif_Set_bc(utau_nst,(/0,1/)) 
     265      Call Agrif_Set_bc(vtau_nst,(/0,1/)) 
     266      Call Agrif_Set_bc(taum_nst,(/0,1/)) 
     267      Call Agrif_Set_bc(qsr_nst,(/0,1/)) 
     268      Call Agrif_Set_bc(qns_nst,(/0,1/)) 
     269      Call Agrif_Set_bc(emp_nst,(/0,1/)) 
     270      Call Agrif_Set_bc(emps_nst,(/0,1/)) 
     271      Call Agrif_Set_bc(wndm_nst,(/0,1/)) 
     272      Call Agrif_Set_bc(fri_nst,(/0,1/)) 
     273      Call Agrif_Set_bc(tag_nst,(/0,1/)) 
     274#endif 
     275 
    210276      ! 5. Update type 
    211277      !---------------  
     
    229295      Call Agrif_Set_Updatetype(e1u,update1 = Agrif_Update_Copy, update2=Agrif_Update_Average) 
    230296      Call Agrif_Set_Updatetype(e2v,update1 = Agrif_Update_Average, update2=Agrif_Update_Copy) 
     297 
     298#if defined key_lim2 && defined key_agrif_nolim 
     299      Call Agrif_Set_Updatetype(utau_nst,update1 = Agrif_Update_Copy, update2 = Agrif_Update_Average) 
     300      Call Agrif_Set_Updatetype(vtau_nst,update1 = Agrif_Update_Average, update2 = Agrif_Update_Copy) 
     301      Call Agrif_Set_Updatetype(taum_nst , update = AGRIF_Update_Average) 
     302      Call Agrif_Set_Updatetype(qsr_nst , update = AGRIF_Update_Average) 
     303      Call Agrif_Set_Updatetype(qns_nst , update = AGRIF_Update_Average) 
     304      Call Agrif_Set_Updatetype(emp_nst , update = AGRIF_Update_Average) 
     305      Call Agrif_Set_Updatetype(emps_nst, update = AGRIF_Update_Average) 
     306      Call Agrif_Set_Updatetype(wndm_nst, update = AGRIF_Update_Average) 
     307      Call Agrif_Set_Updatetype(fri_nst, update = AGRIF_Update_Average) 
     308      Call Agrif_Set_Updatetype(tag_nst , update = AGRIF_Update_Average) 
     309#endif 
    231310 
    232311      ! 6. First interpolations of potentially non zero fields 
     
    248327      Call Agrif_Bc_variable(tabtrtemp,trn,calledweight=1.) 
    249328      Call Agrif_Bc_variable(tabtrtemp,tra,calledweight=1.,procname=interptrn) 
     329#endif 
     330 
     331#if defined key_lim2 && defined key_agrif_nolim 
     332 
     333!     Call Agrif_Interp_variable(tabflxtemp,utau_nst,procname=interputau) 
     334!     Call Agrif_Interp_variable(tabflxtemp,vtau_nst,procname=interpvtau) 
     335      Call Agrif_Interp_variable(tabflxtemp,utau_nst) 
     336      Call Agrif_Interp_variable(tabflxtemp,vtau_nst) 
     337      Call Agrif_Interp_variable(tabflxtemp,taum_nst) 
     338      Call Agrif_Interp_variable(tabflxtemp,qsr_nst) 
     339      Call Agrif_Interp_variable(tabflxtemp,qns_nst) 
     340      Call Agrif_Interp_variable(tabflxtemp,emp_nst) 
     341      Call Agrif_Interp_variable(tabflxtemp,emps_nst) 
     342      Call Agrif_Interp_variable(tabflxtemp,wndm_nst) 
     343      Call Agrif_Interp_variable(tabflxtemp,fri_nst) 
     344      Call Agrif_Interp_variable(tabflxtemp,tag_nst) 
     345!     Call Agrif_Bc_variable(tabflxtemp,utau_nst,calledweight=1.,procname=interputau) 
     346!     Call Agrif_Bc_variable(tabflxtemp,vtau_nst,calledweight=1.,procname=interpvtau) 
     347      Call Agrif_Bc_variable(tabflxtemp,utau_nst,calledweight=1.) 
     348      Call Agrif_Bc_variable(tabflxtemp,vtau_nst,calledweight=1.) 
     349      Call Agrif_Bc_variable(tabflxtemp,taum_nst,calledweight=1.) 
     350      Call Agrif_Bc_variable(tabflxtemp,qsr_nst,calledweight=1.) 
     351      Call Agrif_Bc_variable(tabflxtemp,qns_nst,calledweight=1.) 
     352      Call Agrif_Bc_variable(tabflxtemp,emp_nst,calledweight=1.) 
     353      Call Agrif_Bc_variable(tabflxtemp,emps_nst,calledweight=1.) 
     354      Call Agrif_Bc_variable(tabflxtemp,wndm_nst,calledweight=1.) 
     355      Call Agrif_Bc_variable(tabflxtemp,fri_nst,calledweight=1.) 
     356      Call Agrif_Bc_variable(tabflxtemp,tag_nst,calledweight=1.) 
    250357#endif 
    251358      Agrif_UseSpecialValue = .FALSE. 
  • branches/dev_005_AWL/NEMO/OPA_SRC/SBC/sbcmod.F90

    r1725 r1786  
    3737   USE iom 
    3838   USE in_out_manager  ! I/O manager 
     39#if defined key_agrif_nolim 
     40   USE agrif_nolim 
     41#endif 
    3942 
    4043   IMPLICIT NONE 
     
    97100          nn_ice      =   0 
    98101      ENDIF 
     102 
     103#if defined key_agrif && defined key_agrif_nolim    
     104      IF ( .NOT. Agrif_Root() ) THEN    
     105         IF( nn_ice /= 0 ) CALL ctl_stop("sbcmod: non-zero nn_ice in nest model when interpolating")  
     106         IF( ln_ssr )      CALL ctl_stop("sbcmod: surface relaxation not valid when interpolating") 
     107         IF( nn_fwb  /= 0) CALL ctl_stop("sbcmod: adjustment of freshwater budget not valid when interpolating") 
     108      ENDIF 
     109      ! 
     110      CALL agrif_nolim_init() 
     111      ! 
     112#endif 
    99113       
    100114      ! Control print 
     
    199213      ! --------------- 
    200214          
     215#if key_agrif && defined key_agrif_nolim 
     216 
     217      IF( Agrif_Root() ) THEN 
     218         ! 
     219         CALL agrif_nolim_extrap( kt ) 
     220         ! 
     221      ELSE 
     222         ! 
     223         CALL agrif_nolim_flx( kt ) 
     224         ! 
     225      ENDIF 
     226 
     227#else 
     228 
    201229      SELECT CASE( nsbc )                        ! Compute ocean surface boundary condition 
    202230      !                                          ! (i.e. utau,vtau, qns, qsr, emp, emps) 
     
    237265      IF( nclosea == 1 )   CALL sbc_clo( kt )                   ! treatment of closed sea in the model domain  
    238266      !                                                         ! (update freshwater fluxes) 
     267#endif 
    239268      ! 
    240269      IF( MOD( kt-1, nn_fsbc ) == 0 ) THEN 
Note: See TracChangeset for help on using the changeset viewer.