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 3738 for branches – NEMO

Changeset 3738 for branches


Ignore:
Timestamp:
2012-12-14T13:28:37+01:00 (11 years ago)
Author:
cetlod
Message:

dev_r3411_CNRS4_IOCRS : some corrections

Location:
branches/2013/dev_r3411_CNRS4_IOCRS/NEMOGCM
Files:
10 added
1 deleted
10 edited

Legend:

Unmodified
Added
Removed
  • branches/2013/dev_r3411_CNRS4_IOCRS/NEMOGCM/CONFIG/ORCA2_LIM_CRS/MY_SRC/dom_oce.F90

    r3622 r3738  
    99   !!            4.0  ! 2011-01  (A. R. Porter, STFC Daresbury) dynamical allocation 
    1010   !!                 ! 2012-06  (J. Simeon) Add ln_crs to dom_nam 
    11    !!                 !          Add npiglo, npjglo i.e. non-parameter references to jpiglo,jpjglo 
    1211   !!---------------------------------------------------------------------- 
    1312 
     
    9493   INTEGER, PUBLIC ::   nbse, nbsw        !: logical of south east & south west processor 
    9594   INTEGER, PUBLIC ::   nidom             !: ??? 
    96    INTEGER, PUBLIC ::   npiglo, npjglo    !: non-parameter reference to jpiglo, jpjglo 
    9795 
    9896   INTEGER, PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:) ::   mig        !: local  ==> global domain i-index 
     
    192190   REAL(wp), PUBLIC, ALLOCATABLE, SAVE, DIMENSION(:,:,:) :: tmask, umask, vmask, fmask   !: land/ocean mask at T-, U-, V- and F-pts 
    193191 
    194    REAL(wp), PUBLIC, DIMENSION(jpiglo) ::   tpol, fpol          !: north fold mask (jperio= 3 or 4) 
     192   REAL(wp), PUBLIC, DIMENSION(jpidta) ::   tpol, fpol          !: north fold mask (jperio= 3 or 4) 
    195193 
    196194#if defined key_noslip_accurate 
  • branches/2013/dev_r3411_CNRS4_IOCRS/NEMOGCM/CONFIG/ORCA2_LIM_CRS/MY_SRC/iom.F90

    r3622 r3738  
    77   !!            9.0  ! 06 02  (S. Masson) Adaptation to NEMO 
    88   !!             "   ! 07 07  (D. Storkey) Changes to iom_gettime 
    9    !!                 ! 12 06  (J. Simeon, G. Madec, C. Ethe) sub parameter 
    10    !!                 !         jpiglo, jpjglo with non-parameter npiglo, npjglo 
    119   !!                 ! 12 07  - add coarse grid definitions (modified iodef.xml) 
    1210   !!                           
     
    10261024      REAL(wp), DIMENSION(jpi,jpj), INTENT(in) ::   plat 
    10271025 
    1028       CALL event__set_grid_dimension( cdname, npiglo, npjglo) 
     1026      CALL event__set_grid_dimension( cdname, jpiglo, jpjglo) 
    10291027      CALL event__set_grid_domain( cdname, nlei-nldi+1, nlej-nldj+1, nimpp+nldi-1, njmpp+nldj-1, & 
    10301028         &                         plon(nldi:nlei, nldj:nlej), plat(nldi:nlei, nldj:nlej) ) 
     
    10441042      REAL(wp), DIMENSION(jpi_crs,jpj_crs), INTENT(in) ::   plat 
    10451043 
    1046  
    1047       !! Save the parent grid information 
    1048       jpi_full    = jpi  
    1049       jpj_full    = jpj 
    1050       jpim1_full  = jpim1 
    1051       jpjm1_full  = jpjm1 
    1052       nperio_full = nperio 
    1053  
    1054       npolj_full  = npolj  
    1055       jpnij_full  = jpnij 
    1056       narea_full  = narea 
    1057       npiglo_full = jpiglo  
    1058       npjglo_full = jpjglo 
    1059  
    1060       nlcj_full   = nlcj  
    1061       nlci_full   = nlci 
    1062       nldi_full   = nldi 
    1063       nlei_full   = nlei 
    1064       nlej_full   = nlej 
    1065       nldj_full   = nldj 
    1066  
    1067       !! Switch to coarse grid domain 
    1068       jpi    = jpi_crs  
    1069       jpj    = jpj_crs 
    1070       jpim1  = jpi_crsm1 
    1071       jpjm1  = jpj_crsm1 
    1072       nperio = nperio_crs 
    1073  
    1074       npolj  = npolj_crs  
    1075       jpnij  = jpnij_crs 
    1076       narea  = narea_crs 
    1077       npiglo = jpiglo_crs  
    1078       npjglo = jpjglo_crs 
    1079   
    1080       nlcj   = nlcj_crs  
    1081       nlci   = nlci_crs 
    1082       nldi   = nldi_crs 
    1083       nlei   = nlei_crs 
    1084       nlej   = nlej_crs 
    1085       nldj   = nldj_crs 
     1044      CALL dom_grid_crs   ! Save the parent grid information  & Switch to coarse grid domain 
    10861045       
    10871046      CALL set_grid( cdname, plon, plat ) 
    10881047 
    1089       !! Return to parent grid domain 
    1090       jpi    = jpi_full  
    1091       jpj    = jpj_full 
    1092       jpim1  = jpim1_full 
    1093       jpjm1  = jpjm1_full 
    1094       nperio = nperio_full 
    1095  
    1096       npolj  = npolj_full  
    1097       jpnij  = jpnij_full 
    1098       narea  = narea_full 
    1099       npiglo = npiglo_full  
    1100       npjglo = npjglo_full 
    1101   
    1102       nlcj   = nlcj_full  
    1103       nlci   = nlci_full 
    1104       nldi   = nldi_full 
    1105       nlei   = nlei_full 
    1106       nlej   = nlej_full 
    1107       nldj   = nldj_full 
     1048      CALL dom_grid_glo   ! Return to parent grid domain 
    11081049 
    11091050   END SUBROUTINE setgrid_crs 
  • branches/2013/dev_r3411_CNRS4_IOCRS/NEMOGCM/CONFIG/ORCA2_LIM_CRS/MY_SRC/par_oce.F90

    r3622 r3738  
    9191   !!   default option  :                               small closed basin 
    9292   !!--------------------------------------------------------------------- 
    93    CHARACTER(len=16), PUBLIC, PARAMETER ::   cp_cfg = "default"   !: name of the configuration 
    94    INTEGER          , PUBLIC, PARAMETER ::   jp_cfg = 0           !: resolution of the configuration 
     93   CHARACTER(len=16), PUBLIC ::   cp_cfg = "default"   !: name of the configuration 
     94   INTEGER          , PUBLIC ::   jp_cfg = 0           !: resolution of the configuration 
    9595 
    9696   ! data size                                       !!! * size of all input files * 
     
    104104 
    105105   ! zoom starting position  
    106    INTEGER, PUBLIC, PARAMETER ::   jpizoom =   1      !: left bottom (i,j) indices of the zoom 
    107    INTEGER, PUBLIC, PARAMETER ::   jpjzoom =   1      !: in data domain indices 
     106   INTEGER, PUBLIC ::   jpizoom =   1      !: left bottom (i,j) indices of the zoom 
     107   INTEGER, PUBLIC ::   jpjzoom =   1      !: in data domain indices 
    108108 
    109109   ! Domain characteristics 
    110    INTEGER, PUBLIC, PARAMETER ::   jperio  =  0       !: lateral cond. type (between 0 and 6) 
     110   INTEGER, PUBLIC ::   jperio  =  0       !: lateral cond. type (between 0 and 6) 
    111111   !                                                  !  = 0 closed                 ;   = 1 cyclic East-West 
    112112   !                                                  !  = 2 equatorial symmetric   ;   = 3 North fold T-point pivot 
  • branches/2013/dev_r3411_CNRS4_IOCRS/NEMOGCM/CONFIG/ORCA2_LIM_CRS/MY_SRC/step.F90

    r3622 r3738  
    170170      IF( lk_diaharm )   CALL dia_harm( kstp )        ! Tidal harmonic analysis 
    171171                         CALL dia_wri( kstp )         ! ocean model: outputs 
    172 !jes      IF( ln_crs     )   CALL crs_dia_wri( kstp )     ! ocean model: output on coarsened grid 
     172      IF( ln_crs     )   CALL crs_dia_wri( kstp )     ! ocean model: output on coarsened grid 
    173173 
    174174 
  • branches/2013/dev_r3411_CNRS4_IOCRS/NEMOGCM/CONFIG/ORCA2_LIM_CRS/MY_SRC/step_oce.F90

    r3622 r3738  
    9191   USE flo_oce          ! floats variables 
    9292   USE floats           ! floats computation               (flo_stp routine) 
    93 !jes   USE crsdiawri        ! Standard output on coarse grid   (crs_dia_wri routine) 
     93   USE crsdiawri        ! Standard output on coarse grid   (crs_dia_wri routine) 
    9494 
    9595   USE asminc           ! assimilation increments      (tra_asm_inc routine) 
  • branches/2013/dev_r3411_CNRS4_IOCRS/NEMOGCM/NEMO/OPA_SRC/CRS/crs_dom.F90

    r3735 r3738  
    77   !!  History     2012-06  Editing  (J. Simeon, G. Madec, C. Ethe) Original code 
    88   !!---------------------------------------------------------------------- 
    9    USE dom_oce,  ONLY: jpk         ! For parameters in par_oce (jperio, lk_vvl)   
    10    USE par_kind, ONLY: wp 
    11    USE par_oce,  ONLY: jpts 
     9   USE par_oce   
     10   USE dom_oce,  ONLY: nperio, narea, npolj, nlci, nlcj, nldi, nldj, nlei, nlej 
    1211 
    1312   IMPLICIT NONE 
     
    1514 
    1615   PUBLIC crs_dom_alloc  ! Called from crsini.F90 
     16   PUBLIC dom_grid_glo    
     17   PUBLIC dom_grid_crs    
    1718 
    1819      ! Domain variables 
     
    2829      INTEGER  ::  nperio_full, nperio_crs      !: jperio of parent and coarse grids 
    2930      INTEGER  ::  npolj_full, npolj_crs        !: north fold mark 
    30       INTEGER  ::  npiglo_full, npiglo_crs      !: jpiglo 
    31       INTEGER  ::  npjglo_full, npjglo_crs      !: jpjglo 
     31      INTEGER  ::  jpiglo_full, jpjglo_full     !: jpiglo / jpjglo 
    3232      INTEGER  ::  nlci_full, nlcj_full         !: i-, j-dimension of local or sub domain on parent grid 
    3333      INTEGER  ::  nldi_full, nldj_full         !: starting indices of internal sub-domain on parent grid 
     
    242242   END FUNCTION crs_dom_alloc 
    243243     
     244   SUBROUTINE dom_grid_glo 
     245      !!-------------------------------------------------------------------- 
     246      !!                       ***  MODULE dom_grid_glo  *** 
     247      !! 
     248      !! ** Purpose : +Return back to parent grid domain  
     249      !!--------------------------------------------------------------------- 
     250 
     251      !                         Return to parent grid domain 
     252      jpi    = jpi_full 
     253      jpj    = jpj_full 
     254      jpim1  = jpim1_full 
     255      jpjm1  = jpjm1_full 
     256      nperio = nperio_full 
     257 
     258      npolj  = npolj_full 
     259      jpnij  = jpnij_full 
     260      narea  = narea_full 
     261      jpiglo = jpiglo_full 
     262      jpjglo = jpjglo_full 
     263 
     264      nlcj   = nlcj_full 
     265      nlci   = nlci_full 
     266      nldi   = nldi_full 
     267      nlei   = nlei_full 
     268      nlej   = nlej_full 
     269 
     270      nldj   = nldj_full 
     271 
     272   END SUBROUTINE dom_grid_glo 
     273 
     274   SUBROUTINE dom_grid_crs 
     275      !!-------------------------------------------------------------------- 
     276      !!                       ***  MODULE dom_grid_crs  *** 
     277      !! 
     278      !! ** Purpose :  Save the parent grid information & Switch to coarse grid domain 
     279      !!--------------------------------------------------------------------- 
     280 
     281      !                         Save the parent grid information 
     282      jpi_full    = jpi 
     283      jpj_full    = jpj 
     284      jpim1_full  = jpim1 
     285      jpjm1_full  = jpjm1 
     286      nperio_full = nperio 
     287 
     288      npolj_full  = npolj 
     289      jpnij_full  = jpnij 
     290      narea_full  = narea 
     291      jpiglo_full = jpiglo 
     292      jpjglo_full = jpjglo 
     293 
     294      nlcj_full   = nlcj 
     295      nlci_full   = nlci 
     296      nldi_full   = nldi 
     297      nlei_full   = nlei 
     298      nlej_full   = nlej 
     299      nldj_full   = nldj 
     300 
     301      !                        Switch to coarse grid domain 
     302      jpi    = jpi_crs 
     303      jpj    = jpj_crs 
     304      jpim1  = jpi_crsm1 
     305      jpjm1  = jpj_crsm1 
     306      nperio = nperio_crs 
     307 
     308      npolj  = npolj_crs 
     309      jpnij  = jpnij_crs 
     310      narea  = narea_crs 
     311      jpiglo = jpiglo_crs 
     312      jpjglo = jpjglo_crs 
     313 
     314      nlci   = nlci_crs 
     315      nlcj   = nlcj_crs 
     316      nldi   = nldi_crs 
     317      nlei   = nlei_crs 
     318      nlej   = nlej_crs 
     319 
     320      nldj   = nldj_crs 
     321 
     322   END SUBROUTINE dom_grid_crs 
    244323   !!====================================================================== 
    245324 
  • branches/2013/dev_r3411_CNRS4_IOCRS/NEMOGCM/NEMO/OPA_SRC/CRS/crs_iom.F90

    r3622 r3738  
    8181 
    8282 
    83       !! Save the parent grid information 
    84       jpi_full    = jpi  
    85       jpj_full    = jpj 
    86       jpim1_full  = jpim1 
    87       jpjm1_full  = jpjm1 
    88       nperio_full = nperio 
    89  
    90       npolj_full  = npolj  
    91       jpnij_full  = jpnij 
    92       narea_full  = narea 
    93       npiglo_full = jpiglo  
    94       npjglo_full = jpjglo 
    95  
    96       nlcj_full   = nlcj  
    97       nlci_full   = nlci 
    98       nldi_full   = nldi 
    99       nlei_full   = nlei 
    100       nlej_full   = nlej 
    101       nldj_full   = nldj 
    102  
    103       !! Switch to coarse grid domain 
    104       jpi    = jpi_crs  
    105       jpj    = jpj_crs 
    106       jpim1  = jpi_crsm1 
    107       jpjm1  = jpj_crsm1 
    108       nperio = nperio_crs 
    109  
    110       npolj  = npolj_crs  
    111       jpnij  = jpnij_crs 
    112       narea  = narea_crs 
    113       npiglo = jpiglo_crs  
    114       npjglo = jpjglo_crs  
    115  
    116       nlci   = nlci_crs 
    117       nlcj   = nlcj_crs 
    118       nldi   = nldi_crs 
    119       nlei   = nlei_crs 
    120       nlej   = nlej_crs 
    121  
    122       nldj   = nldj_crs 
    123  
     83      CALL dom_grid_crs   ! Save the parent grid information  & Switch to coarse grid domain 
    12484 
    12585      llnoov = (jpni * jpnj ) == jpnij .AND. .NOT. lk_agrif  
     
    13595      WRITE(numout,*) 'crs_iom_open. after iom_open call kiomid=', kiomid 
    13696 
    137       !! Return to parent grid domain 
    138       jpi    = jpi_full  
    139       jpj    = jpj_full 
    140       jpim1  = jpim1_full 
    141       jpjm1  = jpjm1_full 
    142       nperio = nperio_full 
    143  
    144       npolj  = npolj_full  
    145       jpnij  = jpnij_full 
    146       narea  = narea_full 
    147       npiglo = npiglo_full  
    148       npjglo = npjglo_full  
    149  
    150       nlcj   = nlcj_full  
    151       nlci   = nlci_full 
    152       nldi   = nldi_full 
    153       nlei   = nlei_full 
    154       nlej   = nlej_full 
    155  
    156       nldj   = nldj_full 
     97      CALL dom_grid_glo   ! Return to parent grid domain 
    15798 
    15899   END SUBROUTINE crs_iom_open 
     
    201142      INTEGER               :: itype    ! variable type 
    202143 
    203       !! Save the parent grid information 
    204       jpi_full    = jpi  
    205       jpj_full    = jpj 
    206       jpim1_full  = jpim1 
    207       jpjm1_full  = jpjm1 
    208       nperio_full = nperio 
    209  
    210       npolj_full  = npolj  
    211       jpnij_full  = jpnij 
    212       narea_full  = narea 
    213       npiglo_full = jpiglo  
    214       npjglo_full = jpjglo 
    215  
    216       nlcj_full   = nlcj  
    217       nlci_full   = nlci 
    218       nldi_full   = nldi 
    219       nlei_full   = nlei 
    220       nlej_full   = nlej 
    221       nldj_full   = nldj 
    222  
    223       !! Switch to coarse grid domain 
    224       jpi    = jpi_crs  
    225       jpj    = jpj_crs 
    226       jpim1  = jpi_crsm1 
    227       jpjm1  = jpj_crsm1 
    228       nperio = nperio_crs 
    229  
    230       npolj  = npolj_crs  
    231       jpnij  = jpnij_crs 
    232       narea  = narea_crs 
    233       npiglo = jpiglo_crs  
    234       npjglo = jpjglo_crs 
    235   
    236       nlcj   = nlcj_crs  
    237       nlci   = nlci_crs 
    238       nldi   = nldi_crs 
    239       nlei   = nlei_crs 
    240       nlej   = nlej_crs 
    241       nldj   = nldj_crs 
    242  
     144      CALL dom_grid_crs   ! Save the parent grid information  & Switch to coarse grid domain 
    243145 
    244146      IF(     PRESENT(pv_r0d) ) THEN ; CALL iom_rstput( kt, kwrite, kiomid, cdvar, pv_r0d, ktype ) 
     
    248150      ENDIF 
    249151 
    250       !! Return to parent grid domain 
    251       jpi    = jpi_full  
    252       jpj    = jpj_full 
    253       jpim1  = jpim1_full 
    254       jpjm1  = jpjm1_full 
    255       nperio = nperio_full 
    256  
    257       npolj  = npolj_full  
    258       jpnij  = jpnij_full 
    259       narea  = narea_full 
    260       npiglo = npiglo_full  
    261       npjglo = npjglo_full 
    262   
    263       nlcj   = nlcj_full  
    264       nlci   = nlci_full 
    265       nldi   = nldi_full 
    266       nlei   = nlei_full 
    267       nlej   = nlej_full 
    268       nldj   = nldj_full 
    269  
     152      CALL dom_grid_glo   ! Return to parent grid domain 
    270153  
    271154   END SUBROUTINE crs_iom_rstput 
     
    288171      INTEGER               :: itype    ! variable type 
    289172 
    290       !! Save the parent grid information 
    291       jpi_full    = jpi  
    292       jpj_full    = jpj 
    293       jpim1_full  = jpim1 
    294       jpjm1_full  = jpjm1 
    295       nperio_full = nperio 
    296  
    297       npolj_full  = npolj  
    298       jpnij_full  = jpnij 
    299       narea_full  = narea 
    300       npiglo_full = jpiglo  
    301       npjglo_full = jpjglo 
    302  
    303       nlcj_full   = nlcj  
    304       nlci_full   = nlci 
    305       nldi_full   = nldi 
    306       nlei_full   = nlei 
    307       nlej_full   = nlej 
    308       nldj_full   = nldj 
    309  
    310       !! Switch to coarse grid domain 
    311       jpi    = jpi_crs  
    312       jpj    = jpj_crs 
    313       jpim1  = jpi_crsm1 
    314       jpjm1  = jpj_crsm1 
    315       nperio = nperio_crs 
    316  
    317       npolj  = npolj_crs  
    318       jpnij  = jpnij_crs 
    319       narea  = narea_crs 
    320       npiglo = jpiglo_crs  
    321       npjglo = jpjglo_crs 
    322   
    323       nlcj   = nlcj_crs  
    324       nlci   = nlci_crs 
    325       nldi   = nldi_crs 
    326       nlei   = nlei_crs 
    327       nlej   = nlej_crs 
    328       nldj   = nldj_crs 
     173      CALL dom_grid_crs   ! Save the parent grid information  & Switch to coarse grid domain 
    329174 
    330175      ! variable definition 
     
    335180      ENDIF 
    336181 
    337       !! Return to parent grid domain 
    338       jpi    = jpi_full  
    339       jpj    = jpj_full 
    340       jpim1  = jpim1_full 
    341       jpjm1  = jpjm1_full 
    342       nperio = nperio_full 
    343  
    344       npolj  = npolj_full  
    345       jpnij  = jpnij_full 
    346       narea  = narea_full 
    347       npiglo = npiglo_full  
    348       npjglo = npjglo_full 
    349   
    350       nlcj   = nlcj_full  
    351       nlci   = nlci_full 
    352       nldi   = nldi_full 
    353       nlei   = nlei_full 
    354       nlej   = nlej_full 
    355       nldj   = nldj_full 
     182      CALL dom_grid_glo   ! Return to parent grid domain 
    356183 
    357184   END SUBROUTINE crs_iom_put 
    358185 
    359 !#if defined key_iomput 
    360  
    361 !#endif 
    362  
    363186END MODULE crs_iom 
  • branches/2013/dev_r3411_CNRS4_IOCRS/NEMOGCM/NEMO/OPA_SRC/CRS/crsdiawri.F90

    r3735 r3738  
    465465  !    CALL crs_eos( ztsn, zrhd, zrhop ) 
    466466 
    467       !! Save the parent grid information 
    468       jpi_full    = jpi 
    469       jpj_full    = jpj 
    470       jpim1_full  = jpim1 
    471       jpjm1_full  = jpjm1 
    472  
    473       !! Switch to coarse grid domain 
    474       jpi    = jpi_crs 
    475       jpj    = jpj_crs 
    476       jpim1  = jpi_crsm1 
    477       jpjm1  = jpj_crsm1 
     467      CALL dom_grid_crs   ! Save the parent grid information  & Switch to coarse grid domain 
    478468 
    479469      CALL eos( ztsn, zrhd, zrhop ) 
    480470 
    481       !! Return to parent grid domain 
    482       jpi    = jpi_full  
    483       jpj    = jpj_full 
    484       jpim1  = jpim1_full 
    485       jpjm1  = jpjm1_full 
     471      CALL dom_grid_glo   ! Return to parent grid domain 
    486472 
    487473      zrhdm(:,:,:) = zrhdm(:,:,:) + zrhd 
  • branches/2013/dev_r3411_CNRS4_IOCRS/NEMOGCM/NEMO/OPA_SRC/CRS/crsini.F90

    r3735 r3738  
    116116      jpj_crsm1 = jpj_crs - 1 
    117117 
    118       npiglo_crs  = jpiglo_crs 
    119118      nperio_crs  = jperio 
    120119      npolj_crs   = npolj 
  • branches/2013/dev_r3411_CNRS4_IOCRS/NEMOGCM/NEMO/OPA_SRC/CRS/crslbclnk.F90

    r3622 r3738  
    4040 
    4141      !!---------------------------------------------------------------------- 
    42       !! Save the parent grid information 
    43       jpi_full    = jpi  
    44       jpj_full    = jpj 
    45       jpim1_full  = jpim1 
    46       jpjm1_full  = jpjm1 
    47       nperio_full = nperio 
    4842 
    49       npolj_full  = npolj  
    50       jpnij_full  = jpnij 
    51       narea_full  = narea 
    52       npiglo_full = jpiglo  
    53       npjglo_full = jpjglo 
    54  
    55       nlcj_full   = nlcj  
    56       nlci_full   = nlci 
    57       nldi_full   = nldi 
    58       nlei_full   = nlei 
    59       nlej_full   = nlej 
    60       nldj_full   = nldj 
    61  
    62 !     jpni_full = jpni 
    63  
    64       !! Switch to coarse grid domain 
    65       jpi    = jpi_crs  
    66       jpj    = jpj_crs 
    67       jpim1  = jpi_crsm1 
    68       jpjm1  = jpj_crsm1 
    69       nperio = nperio_crs 
    70  
    71       npolj  = npolj_crs  
    72       jpnij  = jpnij_crs 
    73       narea  = narea_crs 
    74       npiglo = jpiglo_crs  
    75       npjglo = jpjglo_crs  
    76  
    77       nlcj   = nlcj_crs  
    78       nlci   = nlci_crs 
    79       nldi   = nldi_crs 
    80       nlei   = nlei_crs 
    81       nlej   = nlej_crs 
    82       nldj   = nldj_crs 
    83 !     jpni = jpni_crs 
     43      CALL dom_grid_crs   ! Save the parent grid information  & Switch to coarse grid domain 
    8444 
    8545      IF ( PRESENT( pt2d ) )  THEN 
     
    11070      ENDIF 
    11171 
    112       !! Return to parent grid domain 
    113       jpi    = jpi_full  
    114       jpj    = jpj_full 
    115       jpim1  = jpim1_full 
    116       jpjm1  = jpjm1_full 
    117       nperio = nperio_full 
     72      CALL dom_grid_glo   ! Return to parent grid domain 
    11873 
    119       npolj  = npolj_full  
    120       jpnij  = jpnij_full 
    121       narea  = narea_full 
    122       npiglo = npiglo_full  
    123       npjglo = npjglo_full  
    124  
    125       nlcj   = nlcj_full  
    126       nlci   = nlci_full 
    127       nldi   = nldi_full 
    128       nlei   = nlei_full 
    129       nlej   = nlej_full 
    130       nldj   = nldj_full 
    131  
    132 !     jpni = jpni_full 
    13374   END SUBROUTINE crs_lbc_lnk 
    13475 
Note: See TracChangeset for help on using the changeset viewer.