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 8299 for branches/UKMO – NEMO

Changeset 8299 for branches/UKMO


Ignore:
Timestamp:
2017-07-07T17:33:29+02:00 (7 years ago)
Author:
andmirek
Message:

#1882 no need to define context in iodef.xml

Location:
branches/UKMO/dev_r7573_xios_write/NEMOGCM/NEMO/OPA_SRC/IOM
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • branches/UKMO/dev_r7573_xios_write/NEMOGCM/NEMO/OPA_SRC/IOM/in_out_manager.F90

    r8079 r8299  
    153153   LOGICAL       ::   lsp_area = .TRUE.     !: to make a control print over a specific area 
    154154   CHARACTER(lc) ::   cxios_context         !: context name used in xios 
    155    CHARACTER(lc) ::   wxios_context = "nemo_rstw" !: context name used in xios to write restart file 
     155   CHARACTER(lc) ::   wxios_context         !: context name used in xios to write restart file 
    156156 
    157157   !!---------------------------------------------------------------------- 
  • branches/UKMO/dev_r7573_xios_write/NEMOGCM/NEMO/OPA_SRC/IOM/iom.F90

    r8297 r8299  
    9292CONTAINS 
    9393 
    94    SUBROUTINE iom_init( cdname, filename, it )  
     94   SUBROUTINE iom_init( cdname )  
    9595      !!---------------------------------------------------------------------- 
    9696      !!                     ***  ROUTINE   *** 
     
    112112      ! 
    113113      REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: z_bnds 
    114       CHARACTER(len=*), OPTIONAL, INTENT(in)  :: filename  
    115       LOGICAL :: lrst_context              ! is context related to restart 
    116       INTEGER, OPTIONAL :: it              ! timestep when subroutine was called 
    117114      !!---------------------------------------------------------------------- 
    118115#if ! defined key_xios2 
     
    126123      CALL xios_context_initialize(TRIM(clname), mpi_comm_opa) 
    127124      CALL iom_swap( cdname ) 
    128       lrst_context =  (TRIM(cdname) == TRIM(wxios_context)) 
    129125 
    130126      ! calendar parameters 
     
    153149      CALL set_scalar 
    154150 
    155       IF( TRIM(cdname) == TRIM(cxios_context) .OR. lrst_context ) THEN   
    156          CALL set_grid( "T", glamt, gphit, ln_mskland )  
    157          CALL set_grid( "U", glamu, gphiu, ln_mskland ) 
    158          CALL set_grid( "V", glamv, gphiv, ln_mskland ) 
    159          CALL set_grid( "W", glamt, gphit, ln_mskland ) 
     151      IF( TRIM(cdname) == TRIM(cxios_context)) THEN   
     152         CALL set_grid( "T", glamt, gphit, .TRUE. )  
     153         CALL set_grid( "U", glamu, gphiu, .TRUE. ) 
     154         CALL set_grid( "V", glamv, gphiv, .TRUE. ) 
     155         CALL set_grid( "W", glamt, gphit, .TRUE. ) 
    160156         CALL set_grid_znl( gphit ) 
    161          CALL set_grid("N",glamt, gphit, .FALSE.)        ! not masked values 
    162157         ! 
    163          IF( ln_cfmeta .AND. .NOT.lrst_context) THEN   ! Add additional grid metadata 
     158         IF( ln_cfmeta ) THEN   ! Add additional grid metadata 
    164159            CALL iom_set_domain_attr("grid_T", area = e12t(nldi:nlei, nldj:nlej)) 
    165160            CALL iom_set_domain_attr("grid_U", area = e12u(nldi:nlei, nldj:nlej)) 
     
    184179         CALL dom_grid_glo   ! Return to parent grid domain 
    185180         ! 
    186          IF( ln_cfmeta .AND. .NOT.lrst_context) THEN   ! Add additional grid metadata 
     181         IF( ln_cfmeta) THEN   ! Add additional grid metadata 
    187182            CALL iom_set_domain_attr("grid_T", area = e1e2t_crs(nldi:nlei, nldj:nlej)) 
    188183            CALL iom_set_domain_attr("grid_U", area = e1u_crs(nldi:nlei, nldj:nlej) * e2u_crs(nldi:nlei, nldj:nlej)) 
     
    239234      CALL iom_set_axis_attr( "iax_28C", (/ REAL(28,wp) /) ) 
    240235       
    241       ! automatic definitions of some of the xml attributs 
    242       IF( TRIM(cdname) == TRIM(wxios_context)) THEN 
    243 !set which fields are to be read from restart file 
    244        CALL set_rstw_active(filename, it) 
    245       ELSE 
    246        CALL set_xmlatt 
    247       ENDIF 
     236      CALL set_xmlatt 
    248237 
    249238      CALL set_1point 
     
    262251   END SUBROUTINE iom_init 
    263252 
     253   SUBROUTINE iom_rstw_init( cdname, filename, it )  
     254      !!---------------------------------------------------------------------- 
     255      !!                     ***  ROUTINE   *** 
     256      !! 
     257      !! ** Purpose :    
     258      !! 
     259      !!---------------------------------------------------------------------- 
     260      CHARACTER(len=*), INTENT(in)  :: cdname 
     261#if defined key_iomput 
     262#if defined key_xios2 
     263      TYPE(xios_duration) :: dtime    = xios_duration(0, 0, 0, 0, 0, 0) 
     264      TYPE(xios_date)     :: start_date 
     265      TYPE(xios_domaingroup)            :: domaingroup_hdl 
     266      TYPE(xios_domain)                 :: domain_hdl 
     267      TYPE(xios_axisgroup)              :: axisgroup_hdl 
     268      TYPE(xios_axis)                   :: axis_hdl 
     269      TYPE(xios_scalar)                 :: scalar_hdl 
     270      TYPE(xios_scalargroup)            :: scalargroup_hdl 
     271#endif 
     272      CHARACTER(len=128)   :: clname 
     273      INTEGER             :: ji 
     274      ! 
     275      CHARACTER(len=*), OPTIONAL, INTENT(in)  :: filename  
     276      INTEGER, OPTIONAL :: it              ! timestep when subroutine was called 
     277      !!---------------------------------------------------------------------- 
     278 
     279      clname = cdname  
     280      if(lwp) write(numout,*) 'initialize CONTEXT:', TRIM(cdname) 
     281      IF( TRIM(Agrif_CFixed()) /= '0' )   clname = TRIM(Agrif_CFixed())//"_"//TRIM(cdname) 
     282      CALL xios_context_initialize(TRIM(clname), mpi_comm_opa) 
     283      CALL iom_swap( cdname ) 
     284      ! calendar parameters 
     285#if defined key_xios2 
     286      ! Calendar type is now defined in xml file  
     287      SELECT CASE ( nleapy )        ! Choose calendar for IOIPSL 
     288      CASE ( 1)   ; CALL xios_define_calendar( TYPE = "Gregorian", time_origin = xios_date(1900,01,01,00,00,00), & 
     289          &                                    start_date = xios_date(nyear,nmonth,nday,0,0,0) ) 
     290      CASE ( 0)   ; CALL xios_define_calendar( TYPE = "NoLeap"   , time_origin = xios_date(1900,01,01,00,00,00), & 
     291          &                                    start_date = xios_date(nyear,nmonth,nday,0,0,0) ) 
     292      CASE (30)   ; CALL xios_define_calendar( TYPE = "D360"     , time_origin = xios_date(1900,01,01,00,00,00), & 
     293          &                                    start_date = xios_date(nyear,nmonth,nday,0,0,0) ) 
     294      END SELECT 
     295 
     296#endif 
     297      CALL xios_get_handle("domain_definition",domaingroup_hdl) 
     298      CALL xios_add_child(domaingroup_hdl, domain_hdl, "grid_N") 
     299      CALL set_grid("N", glamt, gphit, .FALSE.) 
     300 
     301      CALL xios_get_handle("axis_definition",axisgroup_hdl) 
     302      CALL xios_add_child(axisgroup_hdl, axis_hdl, "deptht") 
     303      CALL xios_set_axis_attr( "deptht", long_name="Vertical levels",  unit="m", positive="down") 
     304      ! vertical grid definition 
     305      CALL iom_set_axis_attr( "deptht", paxis = gdept_1d ) 
     306 
     307      CALL XIOS_GET_HANDLE("scalar_definition",scalargroup_hdl) 
     308      CALL xios_add_child(scalargroup_hdl, scalar_hdl, "grid_scalar") 
     309      CALL xios_set_scalar_attr( "grid_scalar", value=1. ) 
     310 
     311      ! automatic definitions of some of the xml attributs 
     312      IF( TRIM(cdname) == TRIM(wxios_context)) THEN 
     313!set which fields are to be read from restart file 
     314       CALL set_rstw_active(filename, it) 
     315      ENDIF 
     316 
     317      ! end file definition 
     318      dtime%second = rdt 
     319      CALL xios_set_timestep(dtime) 
     320      CALL xios_close_context_definition() 
     321       
     322#endif 
     323 
     324   END SUBROUTINE iom_rstw_init 
     325 
    264326   SUBROUTINE set_rstw_active(rst_file, it) 
    265327!sets enabled = .TRUE. for each field in restart file 
    266328   CHARACTER(len=*) :: rst_file 
    267329   INTEGER, INTENT(in) :: it ! timestep when iom_init was called 
    268    TYPE(xios_field) :: field_hdl 
    269330   TYPE(xios_file) :: file_hdl 
    270331   TYPE(xios_filegroup) :: filegroup_hdl 
     
    285346 
    286347        CALL xios_set_file_attr( "wrestart", name=trim(rst_file)) 
     348        CALL set_numro_active(file_hdl) 
     349 
     350    END SUBROUTINE set_rstw_active 
     351 
     352    SUBROUTINE set_numro_active(file_hdl) 
     353    TYPE(xios_field) :: field_hdl 
     354    TYPE(xios_file) :: file_hdl 
    287355 
    288356        CALL xios_add_child(file_hdl, field_hdl, "rdt") 
    289357        CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    290                   grid_ref = "grid_scalar", operation = "instant") 
     358                  scalar_ref = "grid_scalar", operation = "instant") 
    291359 
    292360        CALL xios_add_child(file_hdl, field_hdl, "rdttra1") 
    293361        CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    294                   grid_ref = "grid_scalar", operation = "instant") 
     362                  scalar_ref = "grid_scalar", operation = "instant") 
    295363 
    296364        CALL xios_add_child(file_hdl, field_hdl, "un") 
    297365        CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    298                   grid_ref = "grid_N_3D", operation = "instant") 
     366                  domain_ref="grid_N", axis_ref="deptht", operation = "instant") 
    299367 
    300368        CALL xios_add_child(file_hdl, field_hdl, "ub") 
    301369        CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    302                   grid_ref = "grid_N_3D", operation = "instant") 
     370                  domain_ref="grid_N", axis_ref="deptht", operation = "instant") 
    303371 
    304372        CALL xios_add_child(file_hdl, field_hdl, "vn") 
    305373        CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    306                   grid_ref = "grid_N_3D", operation = "instant") 
     374                  domain_ref="grid_N", axis_ref="deptht", operation = "instant") 
    307375 
    308376        CALL xios_add_child(file_hdl, field_hdl, "vb") 
    309377        CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    310                   grid_ref = "grid_N_3D", operation = "instant") 
     378                  domain_ref="grid_N", axis_ref="deptht", operation = "instant") 
    311379 
    312380        CALL xios_add_child(file_hdl, field_hdl, "tn") 
    313381        CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    314                   grid_ref = "grid_N_3D", operation = "instant") 
     382                  domain_ref="grid_N", axis_ref="deptht", operation = "instant") 
    315383 
    316384        CALL xios_add_child(file_hdl, field_hdl, "tb") 
    317385        CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    318                   grid_ref = "grid_N_3D", operation = "instant") 
     386                  domain_ref="grid_N", axis_ref="deptht", operation = "instant") 
    319387 
    320388        CALL xios_add_child(file_hdl, field_hdl, "sn") 
    321389        CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    322                   grid_ref = "grid_N_3D", operation = "instant") 
     390                  domain_ref="grid_N", axis_ref="deptht", operation = "instant") 
    323391 
    324392        CALL xios_add_child(file_hdl, field_hdl, "sb") 
    325393        CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    326                   grid_ref = "grid_N_3D", operation = "instant") 
     394                  domain_ref="grid_N", axis_ref="deptht", operation = "instant") 
    327395 
    328396        CALL xios_add_child(file_hdl, field_hdl, "sshn") 
    329397        CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    330                   grid_ref = "grid_N", operation = "instant") 
     398                  domain_ref = "grid_N", operation = "instant") 
    331399 
    332400        CALL xios_add_child(file_hdl, field_hdl, "sshb") 
    333401        CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    334                   grid_ref = "grid_N", operation = "instant") 
     402                  domain_ref = "grid_N", operation = "instant") 
    335403 
    336404        CALL xios_add_child(file_hdl, field_hdl, "hdivn") 
    337405        CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    338                   grid_ref = "grid_N_3D", operation = "instant") 
     406                  domain_ref="grid_N", axis_ref="deptht", operation = "instant") 
    339407 
    340408        CALL xios_add_child(file_hdl, field_hdl, "hdivb") 
    341409        CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    342                   grid_ref = "grid_N_3D", operation = "instant") 
     410                  domain_ref="grid_N", axis_ref="deptht", operation = "instant") 
    343411 
    344412        CALL xios_add_child(file_hdl, field_hdl, "rhop") 
    345413        CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    346                   grid_ref = "grid_N_3D", operation = "instant") 
     414                  domain_ref="grid_N", axis_ref="deptht", operation = "instant") 
    347415 
    348416        CALL xios_add_child(file_hdl, field_hdl, "rotn") 
    349417        CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    350                   grid_ref = "grid_N_3D", operation = "instant") 
     418                  domain_ref="grid_N", axis_ref="deptht", operation = "instant") 
    351419 
    352420        CALL xios_add_child(file_hdl, field_hdl, "rotb") 
    353421        CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    354                   grid_ref = "grid_N_3D", operation = "instant") 
    355  
     422                  domain_ref="grid_N", axis_ref="deptht", operation = "instant") 
    356423 
    357424!in daymod.F90 
    358425           CALL xios_add_child(file_hdl, field_hdl, "kt") 
    359426           CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    360                      grid_ref = "grid_scalar", operation = "instant") 
     427                     scalar_ref = "grid_scalar", operation = "instant") 
    361428 
    362429           CALL xios_add_child(file_hdl, field_hdl, "ndastp") 
    363430           CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    364                      grid_ref = "grid_scalar", operation = "instant") 
     431                     scalar_ref = "grid_scalar", operation = "instant") 
    365432 
    366433           CALL xios_add_child(file_hdl, field_hdl, "adatrj") 
    367434           CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    368                      grid_ref = "grid_scalar", operation = "instant") 
     435                     scalar_ref = "grid_scalar", operation = "instant") 
    369436!end daymod.F90 
    370437!sbcmod.F90 
    371438           CALL xios_add_child(file_hdl, field_hdl, "utau_b") 
    372439           CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    373                      grid_ref = "grid_N", operation = "instant") 
     440                     domain_ref = "grid_N", operation = "instant") 
    374441 
    375442           CALL xios_add_child(file_hdl, field_hdl, "vtau_b") 
    376443           CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    377                      grid_ref = "grid_N", operation = "instant") 
     444                     domain_ref = "grid_N", operation = "instant") 
    378445 
    379446           CALL xios_add_child(file_hdl, field_hdl, "qns_b") 
    380447           CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    381                      grid_ref = "grid_N", operation = "instant") 
     448                     domain_ref = "grid_N", operation = "instant") 
    382449 
    383450           CALL xios_add_child(file_hdl, field_hdl, "emp_b") 
    384451           CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    385                      grid_ref = "grid_N", operation = "instant") 
     452                     domain_ref = "grid_N", operation = "instant") 
    386453 
    387454           CALL xios_add_child(file_hdl, field_hdl, "sfx_b") 
    388455           CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    389                      grid_ref = "grid_N", operation = "instant") 
     456                     domain_ref = "grid_N", operation = "instant") 
    390457!end sbcmod.F90 
    391458!ALL FIELDS ABOUVE ALWAYS 
     
    394461           CALL xios_add_child(file_hdl, field_hdl, "en") 
    395462           CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    396                      grid_ref = "grid_N_3D", operation = "instant") 
     463                     domain_ref="grid_N", axis_ref="deptht", operation = "instant") 
    397464 
    398465           CALL xios_add_child(file_hdl, field_hdl, "avt") 
    399466           CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    400                      grid_ref = "grid_N_3D", operation = "instant") 
     467                     domain_ref="grid_N", axis_ref="deptht", operation = "instant") 
    401468 
    402469           CALL xios_add_child(file_hdl, field_hdl, "avm") 
    403470           CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    404                      grid_ref = "grid_N_3D", operation = "instant") 
     471                     domain_ref="grid_N", axis_ref="deptht", operation = "instant") 
    405472 
    406473           CALL xios_add_child(file_hdl, field_hdl, "avmu") 
    407474           CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    408                      grid_ref = "grid_N_3D", operation = "instant") 
     475                     domain_ref="grid_N", axis_ref="deptht", operation = "instant") 
    409476 
    410477           CALL xios_add_child(file_hdl, field_hdl, "avmv") 
    411478           CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    412                      grid_ref = "grid_N_3D", operation = "instant") 
     479                     domain_ref="grid_N", axis_ref="deptht", operation = "instant") 
    413480 
    414481           CALL xios_add_child(file_hdl, field_hdl, "dissl") 
    415482           CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    416                      grid_ref = "grid_N_3D", operation = "instant") 
     483                     domain_ref="grid_N", axis_ref="deptht", operation = "instant") 
    417484#endif 
    418485!end zdftke.F90 
     
    420487       CALL xios_add_child(file_hdl, field_hdl, "qsr_hc_b") 
    421488       CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    422                      grid_ref = "grid_N_3D" , operation = "instant")         
     489                     domain_ref="grid_N", axis_ref="deptht" , operation = "instant")         
    423490 
    424491       CALL xios_add_child(file_hdl, field_hdl, "fraqsr_1lev") 
    425492       CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    426                      grid_ref = "grid_N", operation = "instant")         
     493                     domain_ref = "grid_N", operation = "instant")         
    427494!END traqsr.F90 
    428495#if defined key_dynspg_flt   ||   defined key_esopa  
     
    430497           CALL xios_add_child(file_hdl, field_hdl, "gcx") 
    431498           CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    432                      grid_ref = "grid_N", operation = "instant") 
     499                     domain_ref = "grid_N", operation = "instant") 
    433500 
    434501           CALL xios_add_child(file_hdl, field_hdl, "gcxb") 
    435502           CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    436                      grid_ref = "grid_N", operation = "instant") 
     503                     domain_ref = "grid_N", operation = "instant") 
    437504!end dynspg_flt.F90 
    438505#endif 
     
    440507           CALL xios_add_child(file_hdl, field_hdl, "sbc_hc_b") 
    441508           CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    442                      grid_ref = "grid_N", operation = "instant") 
     509                     domain_ref = "grid_N", operation = "instant") 
    443510 
    444511           CALL xios_add_child(file_hdl, field_hdl, "sbc_sc_b") 
    445512           CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    446                      grid_ref = "grid_N", operation = "instant") 
     513                     domain_ref = "grid_N", operation = "instant") 
    447514 
    448515           CALL xios_add_child(file_hdl, field_hdl, "fwf_isf_b") 
    449516           CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    450                      grid_ref = "grid_N", operation = "instant") 
     517                     domain_ref = "grid_N", operation = "instant") 
    451518 
    452519           CALL xios_add_child(file_hdl, field_hdl, "isf_sc_b") 
    453520           CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    454                      grid_ref = "grid_N", operation = "instant") 
     521                     domain_ref = "grid_N", operation = "instant") 
    455522 
    456523           CALL xios_add_child(file_hdl, field_hdl, "isf_hc_b") 
    457524           CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    458                      grid_ref = "grid_N", operation = "instant") 
     525                     domain_ref = "grid_N", operation = "instant") 
    459526!trasbc.F90 END 
    460527        IF( lk_oasis) THEN 
     
    463530             CALL xios_add_child(file_hdl, field_hdl, "greenland_icesheet_mass") 
    464531             CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    465                   grid_ref = "grid_scalar", operation = "instant") 
     532                  scalar_ref = "grid_scalar", operation = "instant") 
    466533 
    467534             CALL xios_add_child(file_hdl, field_hdl, "greenland_icesheet_timelapsed") 
    468535             CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    469                   grid_ref = "grid_scalar", operation = "instant") 
     536                  scalar_ref = "grid_scalar", operation = "instant") 
    470537 
    471538             CALL xios_add_child(file_hdl, field_hdl, "greenland_icesheet_mass_roc") 
    472539             CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    473                   grid_ref = "grid_scalar", operation = "instant") 
     540                  scalar_ref = "grid_scalar", operation = "instant") 
    474541 
    475542             CALL xios_add_child(file_hdl, field_hdl, "antarctica_icesheet_mass") 
    476543             CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    477                   grid_ref = "grid_scalar", operation = "instant") 
     544                  scalar_ref = "grid_scalar", operation = "instant") 
    478545 
    479546             CALL xios_add_child(file_hdl, field_hdl, "antarctica_icesheet_timelapsed") 
    480547             CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    481                   grid_ref = "grid_scalar", operation = "instant") 
     548                  scalar_ref = "grid_scalar", operation = "instant") 
    482549 
    483550             CALL xios_add_child(file_hdl, field_hdl, "antarctica_icesheet_mass_roc") 
    484551             CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    485                   grid_ref = "grid_scalar", operation = "instant") 
     552                  scalar_ref = "grid_scalar", operation = "instant") 
    486553          ENDIF 
    487554        ENDIF 
     
    489556        CALL xios_add_child(file_hdl, field_hdl, "rhd") 
    490557        CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    491              grid_ref = "grid_N_3D", operation = "instant") 
     558             domain_ref="grid_N", axis_ref="deptht", operation = "instant") 
    492559#endif 
    493560!dia_hsb_rst 
     
    496563             CALL xios_add_child(file_hdl, field_hdl, "frc_v") 
    497564             CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    498                   grid_ref = "grid_scalar", operation = "instant") 
     565                  scalar_ref = "grid_scalar", operation = "instant") 
    499566 
    500567             CALL xios_add_child(file_hdl, field_hdl, "frc_t") 
    501568             CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    502                   grid_ref = "grid_scalar", operation = "instant") 
     569                  scalar_ref = "grid_scalar", operation = "instant") 
    503570 
    504571             CALL xios_add_child(file_hdl, field_hdl, "frc_s") 
    505572             CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    506                   grid_ref = "grid_scalar", operation = "instant") 
     573                  scalar_ref = "grid_scalar", operation = "instant") 
    507574 
    508575             CALL xios_add_child(file_hdl, field_hdl, "ssh_ini") 
    509576             CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    510                   grid_ref = "grid_N", operation = "instant") 
     577                  domain_ref = "grid_N", operation = "instant") 
    511578 
    512579             CALL xios_add_child(file_hdl, field_hdl, "e3t_ini") 
    513580             CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    514                   grid_ref = "grid_N_3D", operation = "instant") 
     581                  domain_ref="grid_N", axis_ref="deptht", operation = "instant") 
    515582 
    516583             CALL xios_add_child(file_hdl, field_hdl, "hc_loc_ini") 
    517584             CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    518                   grid_ref = "grid_N_3D", operation = "instant") 
     585                  domain_ref="grid_N", axis_ref="deptht", operation = "instant") 
    519586 
    520587             CALL xios_add_child(file_hdl, field_hdl, "sc_loc_ini") 
    521588             CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    522                   grid_ref = "grid_N_3D", operation = "instant") 
     589                  domain_ref="grid_N", axis_ref="deptht", operation = "instant") 
    523590 
    524591 
     
    526593                CALL xios_add_child(file_hdl, field_hdl, "frc_wn_t") 
    527594                CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    528                      grid_ref = "grid_scalar", operation = "instant") 
     595                     scalar_ref = "grid_scalar", operation = "instant") 
    529596 
    530597                CALL xios_add_child(file_hdl, field_hdl, "frc_wn_s") 
    531598                CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    532                      grid_ref = "grid_scalar", operation = "instant") 
     599                     scalar_ref = "grid_scalar", operation = "instant") 
    533600 
    534601                CALL xios_add_child(file_hdl, field_hdl, "ssh_hc_loc_ini") 
    535602                CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    536                      grid_ref = "grid_N", operation = "instant") 
     603                     domain_ref = "grid_N", operation = "instant") 
    537604 
    538605                CALL xios_add_child(file_hdl, field_hdl, "ssh_sc_loc_ini") 
    539606                CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    540                      grid_ref = "grid_N", operation = "instant") 
     607                     domain_ref = "grid_N", operation = "instant") 
    541608 
    542609 
     
    549616             CALL xios_add_child(file_hdl, field_hdl, "fse3t_b") 
    550617             CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    551                   grid_ref = "grid_N_3D", operation = "instant") 
     618                  domain_ref="grid_N", axis_ref="deptht", operation = "instant") 
    552619 
    553620             CALL xios_add_child(file_hdl, field_hdl, "fse3t_n") 
    554621             CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    555                   grid_ref = "grid_N_3D", operation = "instant") 
     622                  domain_ref="grid_N", axis_ref="deptht", operation = "instant") 
    556623 
    557624           IF( lr_vvl_ztilde .OR. lr_vvl_layer ) THEN  ! z_tilde and layer cases ! 
    558625             CALL xios_add_child(file_hdl, field_hdl, "tilde_e3t_b") 
    559626             CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    560                   grid_ref = "grid_N", operation = "instant") 
     627                  domain_ref = "grid_N", operation = "instant") 
    561628 
    562629             CALL xios_add_child(file_hdl, field_hdl, "tilde_e3t_n") 
    563630             CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    564                   grid_ref = "grid_N", operation = "instant") 
     631                  domain_ref = "grid_N", operation = "instant") 
    565632            END IF 
    566633            IF( lr_vvl_ztilde ) THEN                    ! z_tilde case ! 
    567634            CALL xios_add_child(file_hdl, field_hdl, "hdiv_lf") 
    568635            CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    569                      grid_ref = "grid_N", operation = "instant") 
     636                     domain_ref = "grid_N", operation = "instant") 
    570637            ENDIF 
    571638         ENDIF 
     
    575642         CALL xios_add_child(file_hdl, field_hdl, "ub2_b") 
    576643         CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    577               grid_ref = "grid_N", operation = "instant") 
     644              domain_ref = "grid_N", operation = "instant") 
    578645 
    579646         CALL xios_add_child(file_hdl, field_hdl, "vb2_b") 
    580647         CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    581               grid_ref = "grid_N", operation = "instant") 
     648              domain_ref = "grid_N", operation = "instant") 
    582649 
    583650 
     
    585652            CALL xios_add_child(file_hdl, field_hdl, "sshbb_e") 
    586653            CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    587                  grid_ref = "grid_N", operation = "instant") 
     654                 domain_ref = "grid_N", operation = "instant") 
    588655 
    589656            CALL xios_add_child(file_hdl, field_hdl, "ubb_e") 
    590657            CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    591                  grid_ref = "grid_N", operation = "instant") 
     658                 domain_ref = "grid_N", operation = "instant") 
    592659 
    593660            CALL xios_add_child(file_hdl, field_hdl, "vbb_e") 
    594661            CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    595                  grid_ref = "grid_N", operation = "instant") 
     662                 domain_ref = "grid_N", operation = "instant") 
    596663 
    597664            CALL xios_add_child(file_hdl, field_hdl, "sshb_e") 
    598665            CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    599                  grid_ref = "grid_N", operation = "instant") 
     666                 domain_ref = "grid_N", operation = "instant") 
    600667 
    601668            CALL xios_add_child(file_hdl, field_hdl, "ub_e") 
    602669            CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    603                  grid_ref = "grid_N", operation = "instant") 
     670                 domain_ref = "grid_N", operation = "instant") 
    604671 
    605672            CALL xios_add_child(file_hdl, field_hdl, "vb_e") 
    606673            CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    607                  grid_ref = "grid_N", operation = "instant") 
     674                 domain_ref = "grid_N", operation = "instant") 
    608675         ENDIF 
    609676#if defined key_agrif 
     
    612679               CALL xios_add_child(file_hdl, field_hdl, "ub2_i_b") 
    613680               CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    614                     grid_ref = "GRID_N", operation = "instant") 
     681                    domain_ref = "grid_N", operation = "instant") 
    615682 
    616683               CALL xios_add_child(file_hdl, field_hdl, "vb2_i_b") 
    617684               CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    618                     grid_ref = "grid_N", operation = "instant") 
     685                    domain_ref = "grid_N", operation = "instant") 
    619686         ENDIF 
    620687#endif 
     
    625692             CALL xios_add_child(file_hdl, field_hdl, "ssh_ibb") 
    626693             CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    627                      grid_ref = "grid_N", operation = "instant") 
     694                     domain_ref = "grid_N", operation = "instant") 
    628695          ENDIF 
    629696!end sbcapr.F90 
     
    632699             CALL xios_add_child(file_hdl, field_hdl, "rnf_b") 
    633700             CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    634                   grid_ref = "grid_N", operation = "instant") 
     701                  domain_ref = "grid_N", operation = "instant") 
    635702 
    636703             CALL xios_add_child(file_hdl, field_hdl, "rnf_hc_b") 
    637704             CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    638                   grid_ref = "grid_N", operation = "instant") 
     705                  domain_ref = "grid_N", operation = "instant") 
    639706 
    640707             CALL xios_add_child(file_hdl, field_hdl, "rnf_sc_b") 
    641708             CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    642                   grid_ref = "grid_N", operation = "instant") 
     709                  domain_ref = "grid_N", operation = "instant") 
    643710        ENDIF  
    644711!end sbcrnf.F90 
     
    647714             CALL xios_add_child(file_hdl, field_hdl, "nn_fsbc") 
    648715             CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    649                   grid_ref = "grid_scalar", operation = "instant") 
     716                  scalar_ref = "grid_scalar", operation = "instant") 
    650717 
    651718             CALL xios_add_child(file_hdl, field_hdl, "ssu_m") 
    652719             CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    653                   grid_ref = "grid_N", operation = "instant") 
     720                  domain_ref = "grid_N", operation = "instant") 
    654721 
    655722             CALL xios_add_child(file_hdl, field_hdl, "ssv_m") 
    656723             CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    657                   grid_ref = "grid_N", operation = "instant") 
     724                  domain_ref = "grid_N", operation = "instant") 
    658725 
    659726             CALL xios_add_child(file_hdl, field_hdl, "sst_m") 
    660727             CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    661                   grid_ref = "grid_N", operation = "instant") 
     728                  domain_ref = "grid_N", operation = "instant") 
    662729 
    663730             CALL xios_add_child(file_hdl, field_hdl, "sss_m") 
    664731             CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    665                   grid_ref = "grid_N", operation = "instant") 
     732                  domain_ref = "grid_N", operation = "instant") 
    666733 
    667734             CALL xios_add_child(file_hdl, field_hdl, "ssh_m") 
    668735             CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    669                   grid_ref = "grid_N", operation = "instant") 
     736                  domain_ref = "grid_N", operation = "instant") 
    670737 
    671738             CALL xios_add_child(file_hdl, field_hdl, "frq_m") 
    672739             CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    673                      grid_ref = "grid_N", operation = "instant") 
     740                     domain_ref = "grid_N", operation = "instant") 
    674741 
    675742             IF( lk_vvl )  THEN 
    676743                CALL xios_add_child(file_hdl, field_hdl, "e3t_m") 
    677744                CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    678                      grid_ref = "grid_N", operation = "instant") 
     745                     domain_ref = "grid_N", operation = "instant") 
    679746             ENDIF  
    680747        ENDIF 
     
    683750          CALL xios_add_child(file_hdl, field_hdl, "avmb") 
    684751          CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    685                grid_ref = "Vgrid", operation = "instant") 
     752               axis_ref = "deptht", operation = "instant") 
    686753 
    687754          CALL xios_add_child(file_hdl, field_hdl, "avtb") 
    688755          CALL xios_set_attr (field_hdl, enabled = .TRUE., prec = 8,           & 
    689                grid_ref = "Vgrid", operation = "instant") 
     756               axis_ref = "deptht", operation = "instant") 
    690757       ENDIF 
    691758 
    692    END SUBROUTINE set_rstw_active 
     759   END SUBROUTINE set_numro_active 
    693760 
    694761   SUBROUTINE iom_swap( cdname ) 
     
    18711938 
    18721939 
    1873    SUBROUTINE set_grid( cdgrd, plon, plat, lmask ) 
     1940   SUBROUTINE set_grid( cdgrd, plon, plat, lxios ) 
    18741941      !!---------------------------------------------------------------------- 
    18751942      !!                     ***  ROUTINE set_grid  *** 
     
    18841951      REAL(wp), DIMENSION(jpi,jpj,jpk) ::   zmask 
    18851952      INTEGER  :: ni,nj 
    1886       LOGICAL :: lmask 
     1953      LOGICAL :: lxios 
    18871954       
    18881955      ni=nlei-nldi+1 ; nj=nlej-nldj+1 
     
    18941961#endif      
    18951962      CALL iom_set_domain_attr("grid_"//cdgrd, data_dim=2, data_ibegin = 1-nldi, data_ni = jpi, data_jbegin = 1-nldj, data_nj = jpj) 
    1896       CALL iom_set_domain_attr("grid_"//cdgrd, lonvalue = RESHAPE(plon(nldi:nlei, nldj:nlej),(/ ni*nj /)),   & 
     1963      if(.NOT.lxios) CALL iom_set_domain_attr("grid_"//cdgrd, lonvalue = RESHAPE(plon(nldi:nlei, nldj:nlej),(/ ni*nj /)),   & 
    18971964         &                                     latvalue = RESHAPE(plat(nldi:nlei, nldj:nlej),(/ ni*nj /)))   
    18981965 
    1899       IF ( lmask ) THEN 
     1966      IF ( ln_mskland.AND.(.NOT.lxios) ) THEN 
    19001967         ! mask land points, keep values on coast line -> specific mask for U, V and W points 
    19011968         SELECT CASE ( cdgrd ) 
  • branches/UKMO/dev_r7573_xios_write/NEMOGCM/NEMO/OPA_SRC/IOM/restart.F90

    r8208 r8299  
    126126               CALL iom_open( TRIM(clpath)//TRIM(clname), numrow, ldwrt = .TRUE., kiolib = jprstlib ) 
    127127            ELSE 
    128                CALL iom_init( wxios_context, TRIM(clpath)//TRIM(clname) ) 
     128               wxios_context = "rstw_"//TRIM(ADJUSTL(clkt)) 
     129               CALL iom_rstw_init( wxios_context, TRIM(clpath)//TRIM(clname) ) 
    129130               CALL xios_update_calendar(nitrst) 
    130131               CALL iom_swap(      cxios_context          ) 
Note: See TracChangeset for help on using the changeset viewer.