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 2715 for trunk/NEMOGCM/NEMO/OPA_SRC/BDY – NEMO

Ignore:
Timestamp:
2011-03-30T17:58:35+02:00 (13 years ago)
Author:
rblod
Message:

First attempt to put dynamic allocation on the trunk

Location:
trunk/NEMOGCM/NEMO/OPA_SRC/BDY
Files:
4 edited

Legend:

Unmodified
Added
Removed
  • trunk/NEMOGCM/NEMO/OPA_SRC/BDY/bdy_oce.F90

    r2528 r2715  
    1414   USE par_oce         ! ocean parameters 
    1515   USE bdy_par         ! Unstructured boundary parameters 
     16   USE lib_mpp         ! distributed memory computing 
    1617 
    1718   IMPLICIT NONE 
     
    3233   LOGICAL ::   ln_vol  = .false.     !: =T volume correction              
    3334   LOGICAL ::   ln_mask = .false.     !: =T read bdymask from file 
    34    LOGICAL ::   ln_clim = .false.     !: if true, we assume that bdy data files contain  
    35    !                                    !  1 time dump  (-->bdy forcing will be constant)  
    36    !                                    !  or 12 months (-->bdy forcing will be cyclic)  
     35   LOGICAL ::   ln_clim = .false.     !: =T bdy data files contain  1 time dump  (-->bdy forcing will be constant)  
     36   !                                  !                         or 12 months     (-->bdy forcing will be cyclic)  
    3737   LOGICAL ::   ln_dyn_fla  = .false. !: =T Flather boundary conditions on barotropic velocities 
    3838   LOGICAL ::   ln_dyn_frs  = .false. !: =T FRS boundary conditions on velocities 
     
    4040   LOGICAL ::   ln_ice_frs  = .false. !: =T FRS boundary conditions on seaice (leads fraction, ice depth, snow depth) 
    4141   ! 
    42    INTEGER ::   nn_rimwidth = 7         !: boundary rim width 
    43    INTEGER ::   nn_dtactl   = 1          !: = 0 use the initial state as bdy dta or = 1 read it in a NetCDF file 
    44    INTEGER ::   nn_volctl   = 1         !: = 0 the total volume will have the variability of the surface Flux E-P  
    45    !                                    !  = 1 the volume will be constant during all the integration. 
     42   INTEGER ::   nn_rimwidth = 7       !: boundary rim width 
     43   INTEGER ::   nn_dtactl   = 1       !: = 0 use the initial state as bdy dta ; = 1 read it in a NetCDF file 
     44   INTEGER ::   nn_volctl   = 1       !: = 0 the total volume will have the variability of the surface Flux E-P  
     45   !                                  !  = 1 the volume will be constant during all the integration. 
    4646 
    4747   !!---------------------------------------------------------------------- 
    4848   !! Global variables 
    4949   !!---------------------------------------------------------------------- 
    50    REAL(wp), DIMENSION(jpi,jpj) ::   bdytmask   !: Mask defining computational domain at T-points 
    51    REAL(wp), DIMENSION(jpi,jpj) ::   bdyumask   !: Mask defining computational domain at U-points 
    52    REAL(wp), DIMENSION(jpi,jpj) ::   bdyvmask   !: Mask defining computational domain at V-points 
     50   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   bdytmask   !: Mask defining computational domain at T-points 
     51   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   bdyumask   !: Mask defining computational domain at U-points 
     52   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   bdyvmask   !: Mask defining computational domain at V-points 
    5353 
    5454   !!---------------------------------------------------------------------- 
     
    6363   INTEGER, DIMENSION(jpbdim,jpbgrd) ::   nbmap           !: Indices of data in file for data in memory  
    6464     
    65    REAL(wp) ::   bdysurftot                             !: Lateral surface of unstructured open boundary 
     65   REAL(wp) ::   bdysurftot                               !: Lateral surface of unstructured open boundary 
    6666 
    6767   REAL(wp), DIMENSION(jpbdim)        ::   flagu, flagv   !: Flag for normal velocity compnt for velocity components 
     
    7070   REAL(wp), DIMENSION(jpbdim)     ::   sshbdy            !: Now clim of bdy sea surface height (Flather) 
    7171   REAL(wp), DIMENSION(jpbdim)     ::   ubtbdy, vbtbdy    !: Now clim of bdy barotropic velocity components 
    72    REAL(wp), DIMENSION(jpbdim,jpk) ::   tbdy  , sbdy      !: Now clim of bdy temperature and salinity   
    73    REAL(wp), DIMENSION(jpbdim,jpk) ::   ubdy  , vbdy    !: Now clim of bdy velocity components 
     72   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   tbdy  , sbdy      !: Now clim of bdy temperature and salinity   
     73   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:) ::   ubdy  , vbdy    !: Now clim of bdy velocity components 
    7474   REAL(wp), DIMENSION(jpbdim) ::   sshtide               !: Tidal boundary array : SSH 
    7575   REAL(wp), DIMENSION(jpbdim) ::   utide, vtide          !: Tidal boundary array : U and V 
    7676#if defined key_lim2 
    77    REAL(wp), DIMENSION(jpbdim) ::  & 
    78       frld_bdy, hicif_bdy,  & !: Now clim of ice leads fraction, ice   
    79       hsnif_bdy               !: thickness and snow thickness 
     77   REAL(wp), DIMENSION(jpbdim) ::   frld_bdy    !: now ice leads fraction climatology    
     78   REAL(wp), DIMENSION(jpbdim) ::   hicif_bdy   !: Now ice  thickness climatology 
     79   REAL(wp), DIMENSION(jpbdim) ::   hsnif_bdy   !: now snow thickness 
    8080#endif 
     81 
     82   !!---------------------------------------------------------------------- 
     83   !! NEMO/OPA 4.0 , NEMO Consortium (2011) 
     84   !! $Id$  
     85   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
     86   !!---------------------------------------------------------------------- 
     87CONTAINS 
     88 
     89   FUNCTION bdy_oce_alloc() 
     90      !!---------------------------------------------------------------------- 
     91      USE lib_mpp, ONLY: ctl_warn, mpp_sum 
     92      ! 
     93      INTEGER :: bdy_oce_alloc 
     94      !!---------------------------------------------------------------------- 
     95      ! 
     96      ALLOCATE( bdytmask(jpi,jpj) , tbdy(jpbdim,jpk) , sbdy(jpbdim,jpk) ,     & 
     97         &      bdyumask(jpi,jpj) , ubdy(jpbdim,jpk) ,                        & 
     98         &      bdyvmask(jpi,jpj) , vbdy(jpbdim,jpk) ,                    STAT=bdy_oce_alloc ) 
     99         ! 
     100      IF( lk_mpp             )   CALL mpp_sum ( bdy_oce_alloc ) 
     101      IF( bdy_oce_alloc /= 0 )   CALL ctl_warn('bdy_oce_alloc: failed to allocate arrays.') 
     102      ! 
     103   END FUNCTION bdy_oce_alloc 
    81104 
    82105#else 
     
    87110#endif 
    88111 
    89    !!---------------------------------------------------------------------- 
    90    !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
    91    !! $Id$  
    92    !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
    93112   !!====================================================================== 
    94113END MODULE bdy_oce 
  • trunk/NEMOGCM/NEMO/OPA_SRC/BDY/bdydta.F90

    r2528 r2715  
    3535   PUBLIC   bdy_dta_frs      ! routines called by step.F90 
    3636   PUBLIC   bdy_dta_fla  
     37   PUBLIC   bdy_dta_alloc    ! routine called by bdy_init.F90 
    3738 
    3839   INTEGER ::   numbdyt, numbdyu, numbdyv                      ! logical units for T-, U-, & V-points data file, resp. 
     
    4748   REAL(wp) ::  zoffset                                        ! time offset between time origin in file & start time of model run 
    4849 
    49    REAL(wp), DIMENSION(jpbdim,jpk,2) ::   tbdydta, sbdydta     ! time interpolated values of T and S bdy data    
    50    REAL(wp), DIMENSION(jpbdim,jpk,2) ::   ubdydta, vbdydta     ! time interpolated values of U and V bdy data  
     50   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   tbdydta, sbdydta   ! time interpolated values of T and S bdy data    
     51   REAL(wp), ALLOCATABLE, SAVE, DIMENSION(:,:,:) ::   ubdydta, vbdydta   ! time interpolated values of U and V bdy data  
    5152   REAL(wp), DIMENSION(jpbdim,2)     ::   ubtbdydta, vbtbdydta ! Arrays used for time interpolation of bdy data    
    5253   REAL(wp), DIMENSION(jpbdim,2)     ::   sshbdydta            ! bdy data of ssh 
     
    6465   !!---------------------------------------------------------------------- 
    6566CONTAINS 
     67 
     68  FUNCTION bdy_dta_alloc() 
     69     !!---------------------------------------------------------------------- 
     70     USE lib_mpp, ONLY: ctl_warn, mpp_sum 
     71     ! 
     72     INTEGER :: bdy_dta_alloc 
     73     !!---------------------------------------------------------------------- 
     74     ! 
     75     ALLOCATE(tbdydta(jpbdim,jpk,2), sbdydta(jpbdim,jpk,2), & 
     76              ubdydta(jpbdim,jpk,2), vbdydta(jpbdim,jpk,2), Stat=bdy_dta_alloc) 
     77 
     78     IF( lk_mpp           ) CALL mpp_sum ( bdy_dta_alloc ) 
     79     IF(bdy_dta_alloc /= 0) CALL ctl_warn('bdy_dta_alloc: failed to allocate arrays') 
     80 
     81   END FUNCTION bdy_dta_alloc 
     82 
    6683 
    6784   SUBROUTINE bdy_dta_frs( kt ) 
  • trunk/NEMOGCM/NEMO/OPA_SRC/BDY/bdyice.F90

    r2528 r2715  
    1919   USE lbclnk          ! ocean lateral boundary conditions (or mpp link) 
    2020   USE in_out_manager  ! write to numout file 
     21   USE lib_mpp         ! distributed memory computing 
    2122    
    2223   IMPLICIT NONE 
  • trunk/NEMOGCM/NEMO/OPA_SRC/BDY/bdyini.F90

    r2528 r2715  
    2121   USE obc_par         ! ocean open boundary conditions 
    2222   USE bdy_oce         ! unstructured open boundary conditions 
     23   USE bdydta, ONLY: bdy_dta_alloc ! open boundary data 
    2324   USE bdytides        ! tides at open boundaries initialization (tide_init routine) 
    2425   USE in_out_manager  ! I/O units 
     
    3334 
    3435   !!---------------------------------------------------------------------- 
    35    !! NEMO/OPA 3.3 , NEMO Consortium (2010) 
     36   !! NEMO/OPA 4.0 , NEMO Consortium (2011) 
    3637   !! $Id$  
    37    !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 
     38   !! Software governed by the CeCILL licence     (NEMOGCM/NEMO_CeCILL.txt) 
    3839   !!---------------------------------------------------------------------- 
    3940CONTAINS 
     
    4445      !!          
    4546      !! ** Purpose :   Initialization of the dynamics and tracer fields with  
    46       !!      unstructured open boundaries. 
     47      !!              unstructured open boundaries. 
    4748      !! 
    48       !! ** Method  :  Read initialization arrays (mask, indices) to identify  
    49       !!               an unstructured open boundary 
     49      !! ** Method  :   Read initialization arrays (mask, indices) to identify  
     50      !!              an unstructured open boundary 
    5051      !! 
    5152      !! ** Input   :  bdy_init.nc, input file for unstructured open boundaries 
    5253      !!----------------------------------------------------------------------       
    53       INTEGER ::   ii, ij, ik, igrd, ib, ir   ! dummy loop indices 
    54       INTEGER ::   icount, icountr 
    55       INTEGER ::   ib_len, ibr_max 
    56       INTEGER ::   iw, ie, is, in  
    57       INTEGER ::   inum                 ! local logical unit 
    58       INTEGER ::   id_dummy             ! local integers 
    59       INTEGER ::   igrd_start, igrd_end ! start and end of loops on igrd 
     54      INTEGER  ::   ii, ij, ik, igrd, ib, ir   ! dummy loop indices 
     55      INTEGER  ::   icount, icountr, ib_len, ibr_max   ! local integers 
     56      INTEGER  ::   iw, ie, is, in, inum, id_dummy     !   -       - 
     57      INTEGER  ::   igrd_start, igrd_end               !   -       - 
     58      REAL(wp) ::   zefl, zwfl, znfl, zsfl              ! local scalars 
    6059      INTEGER, DIMENSION (2)             ::   kdimsz 
    6160      INTEGER, DIMENSION(jpbdta, jpbgrd) ::   nbidta, nbjdta   ! Index arrays: i and j indices of bdy dta 
    6261      INTEGER, DIMENSION(jpbdta, jpbgrd) ::   nbrdta           ! Discrete distance from rim points 
    63       REAL(wp) :: zefl, zwfl, znfl, zsfl                       ! temporary scalars 
    64       REAL(wp) , DIMENSION(jpidta,jpjdta) ::   zmask           ! global domain mask 
    65       REAL(wp) , DIMENSION(jpbdta,1)      ::   zdta            ! temporary array  
    66       CHARACTER(LEN=80),DIMENSION(6)      ::   clfile 
     62      REAL(wp), DIMENSION(jpidta,jpjdta) ::   zmask            ! global domain mask 
     63      REAL(wp), DIMENSION(jpbdta,1)      ::   zdta             ! temporary array  
     64      CHARACTER(LEN=80),DIMENSION(6)     ::   clfile 
    6765      !! 
    68       NAMELIST/nambdy/cn_mask, cn_dta_frs_T, cn_dta_frs_U, cn_dta_frs_V,          & 
    69          &            cn_dta_fla_T, cn_dta_fla_U, cn_dta_fla_V,              & 
    70          &            ln_tides, ln_clim, ln_vol, ln_mask,                & 
    71          &            ln_dyn_fla, ln_dyn_frs, ln_tra_frs,ln_ice_frs,     & 
     66      NAMELIST/nambdy/cn_mask, cn_dta_frs_T, cn_dta_frs_U, cn_dta_frs_V,   & 
     67         &            cn_dta_fla_T, cn_dta_fla_U, cn_dta_fla_V,            & 
     68         &            ln_tides, ln_clim, ln_vol, ln_mask,                  & 
     69         &            ln_dyn_fla, ln_dyn_frs, ln_tra_frs,ln_ice_frs,       & 
    7270         &            nn_dtactl, nn_rimwidth, nn_volctl 
    7371      !!---------------------------------------------------------------------- 
     
    7775      IF(lwp) WRITE(numout,*) '~~~~~~~~' 
    7876      ! 
     77      !                                      ! allocate bdy_oce arrays 
     78      IF( bdy_oce_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'bdy_init : unable to allocate oce arrays' ) 
     79      IF( bdy_dta_alloc() /= 0 )   CALL ctl_stop( 'STOP', 'bdy_init : unable to allocate dta arrays' ) 
     80 
    7981      IF( jperio /= 0 )   CALL ctl_stop( 'Cyclic or symmetric,',   & 
    8082         &                               ' and unstructured open boundary condition are not compatible' ) 
Note: See TracChangeset for help on using the changeset viewer.