Changeset 9079
- Timestamp:
- 2017-12-15T15:43:43+01:00 (7 years ago)
- Location:
- branches/2017/dev_merge_2017/NEMOGCM/TOOLS/DOMAINcfg
- Files:
-
- 6 edited
Legend:
- Unmodified
- Added
- Removed
-
branches/2017/dev_merge_2017/NEMOGCM/TOOLS/DOMAINcfg/README
r7828 r9079 22 22 = HOW TO USE 23 23 ================================ 24 ::: VERY IMPORTANT PRE-REQUIRED :::25 0) pre-required: this tool needs xios126 27 (download http://forge.ipsl.jussieu.fr/ioserver/svn/XIOS/branchs/xios-1.028 DOMAINcfg tool is working with revision 703 of xios)29 30 24 1) copy in DOMAINcfg directory namelist_cfg all settings (that you had in 3.6_stable) of the configuration for which you want prepare domain_cfg.nc file 31 IMPORTANT : keep the namelist_ref committed inchanged. 25 IMPORTANT : keep the namelist_ref committed inchanged. !!! 32 26 33 27 NEW OPTION ln_e3_dep in the namelist_ref: -
branches/2017/dev_merge_2017/NEMOGCM/TOOLS/DOMAINcfg/src/domwri.f90
r6984 r9079 22 22 USE wrk_nemo ! Memory allocation 23 23 USE timing ! Timing 24 USE phycst 24 25 25 26 IMPLICIT NONE -
branches/2017/dev_merge_2017/NEMOGCM/TOOLS/DOMAINcfg/src/in_out_manager.f90
r6951 r9079 132 132 LOGICAL :: lwp = .FALSE. !: boolean : true on the 1st processor only .OR. ln_ctl 133 133 LOGICAL :: lsp_area = .TRUE. !: to make a control print over a specific area 134 CHARACTER(lc) :: cxios_context !: context name used in xios135 134 136 135 !!---------------------------------------------------------------------- -
branches/2017/dev_merge_2017/NEMOGCM/TOOLS/DOMAINcfg/src/iom.f90
r6951 r9079 8 8 !! 3.0 ! 2007-07 (D. Storkey) Changes to iom_gettime 9 9 !! 3.4 ! 2012-12 (R. Bourdalle-Badie and G. Reffray) add C1D case 10 !! 3.6 ! 2014-15 DIMG format removed11 10 !!-------------------------------------------------------------------- 12 11 … … 24 23 USE iom_nf90 ! NetCDF format with native NetCDF library 25 24 USE in_out_manager ! I/O manager 26 USE lib_mpp ! MPP library 27 USE domngb ! ocean space and time domain 28 USE phycst ! physical constants 29 USE xios 30 USE ioipsl, ONLY : ju2ymds ! for calendar 25 USE lib_mpp ! MPP library 31 26 32 27 IMPLICIT NONE 33 28 PUBLIC ! must be public to be able to access iom_def through iom 34 29 35 36 LOGICAL, PUBLIC, PARAMETER :: lk_iomput = .TRUE. !: iom_put flag 37 38 39 30 LOGICAL, PUBLIC, PARAMETER :: lk_iomput = .FALSE. !: iom_put flag 40 31 PUBLIC iom_init, iom_swap, iom_open, iom_close, iom_setkt, iom_varid, iom_get, iom_gettime, iom_rstput, iom_put 41 32 PUBLIC iom_getatt, iom_use, iom_context_finalize … … 44 35 PRIVATE iom_g0d, iom_g1d, iom_g2d, iom_g3d, iom_get_123d 45 36 PRIVATE iom_p1d, iom_p2d, iom_p3d 46 47 PRIVATE iom_set_domain_attr, iom_set_axis_attr, iom_set_field_attr, iom_set_file_attr, iom_get_file_attr, iom_set_grid_attr48 PRIVATE set_grid, set_grid_bounds, set_scalar, set_xmlatt, set_mooring, iom_update_file_name, iom_sdate49 50 37 51 38 INTERFACE iom_get … … 64 51 !!---------------------------------------------------------------------- 65 52 !! NEMO/OPA 3.3 , NEMO Consortium (2010) 66 !! $Id: iom.F90 6519 2016-05-11 10:50:34Z timgraham$53 !! $Id: iom.F90 8572 2017-09-28 08:27:06Z cbricaud $ 67 54 !! Software governed by the CeCILL licence (NEMOGCM/NEMO_CeCILL.txt) 68 55 !!---------------------------------------------------------------------- … … 78 65 !!---------------------------------------------------------------------- 79 66 CHARACTER(len=*), INTENT(in) :: cdname 80 81 TYPE(xios_time) :: dtime = xios_time(0, 0, 0, 0, 0, 0)82 CHARACTER(len=19) :: cldate83 CHARACTER(len=10) :: clname84 INTEGER :: ji85 !86 REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: z_bnds87 !!----------------------------------------------------------------------88 89 ALLOCATE( z_bnds(jpk,2) )90 91 clname = cdname92 IF( TRIM(Agrif_CFixed()) /= '0' ) clname = TRIM(Agrif_CFixed())//"_"//TRIM(cdname)93 CALL xios_context_initialize(TRIM(clname), mpi_comm_opa)94 CALL iom_swap( cdname )95 96 ! calendar parameters97 SELECT CASE ( nleapy ) ! Choose calendar for IOIPSL98 CASE ( 1) ; CALL xios_set_context_attr(TRIM(clname), calendar_type= "Gregorian")99 CASE ( 0) ; CALL xios_set_context_attr(TRIM(clname), calendar_type= "NoLeap")100 CASE (30) ; CALL xios_set_context_attr(TRIM(clname), calendar_type= "D360")101 END SELECT102 WRITE(cldate,"(i4.4,'-',i2.2,'-',i2.2,' ',i2.2,':',i2.2,':00')") nyear,nmonth,nday,nhour,nminute103 CALL xios_set_context_attr(TRIM(clname), start_date=cldate )104 105 ! horizontal grid definition106 CALL set_scalar107 108 IF( TRIM(cdname) == TRIM(cxios_context) ) THEN109 CALL set_grid( "T", glamt, gphit )110 CALL set_grid( "U", glamu, gphiu )111 CALL set_grid( "V", glamv, gphiv )112 CALL set_grid( "W", glamt, gphit )113 CALL set_grid_znl( gphit )114 !115 IF( ln_cfmeta ) THEN ! Add additional grid metadata116 CALL iom_set_domain_attr("grid_T", area = e1e2t(nldi:nlei, nldj:nlej))117 CALL iom_set_domain_attr("grid_U", area = e1e2u(nldi:nlei, nldj:nlej))118 CALL iom_set_domain_attr("grid_V", area = e1e2v(nldi:nlei, nldj:nlej))119 CALL iom_set_domain_attr("grid_W", area = e1e2t(nldi:nlei, nldj:nlej))120 CALL set_grid_bounds( "T", glamf, gphif, glamt, gphit )121 CALL set_grid_bounds( "U", glamv, gphiv, glamu, gphiu )122 CALL set_grid_bounds( "V", glamu, gphiu, glamv, gphiv )123 CALL set_grid_bounds( "W", glamf, gphif, glamt, gphit )124 ENDIF125 ENDIF126 127 ! vertical grid definition128 CALL iom_set_axis_attr( "deptht", gdept_1d )129 CALL iom_set_axis_attr( "depthu", gdept_1d )130 CALL iom_set_axis_attr( "depthv", gdept_1d )131 CALL iom_set_axis_attr( "depthw", gdepw_1d )132 133 ! Add vertical grid bounds134 z_bnds(: ,1) = gdepw_1d(:)135 z_bnds(1:jpkm1,2) = gdepw_1d(2:jpk)136 z_bnds(jpk: ,2) = gdepw_1d(jpk) + e3t_1d(jpk)137 CALL iom_set_axis_attr( "deptht", bounds=z_bnds )138 CALL iom_set_axis_attr( "depthu", bounds=z_bnds )139 CALL iom_set_axis_attr( "depthv", bounds=z_bnds )140 z_bnds(: ,2) = gdept_1d(:)141 z_bnds(2:jpk,1) = gdept_1d(1:jpkm1)142 z_bnds(1 ,1) = gdept_1d(1) - e3w_1d(1)143 CALL iom_set_axis_attr( "depthw", bounds=z_bnds )144 145 CALL iom_set_axis_attr( "iax_20C", (/ REAL(20,wp) /) )146 CALL iom_set_axis_attr( "iax_28C", (/ REAL(28,wp) /) )147 148 ! automatic definitions of some of the xml attributs149 CALL set_xmlatt150 151 ! end file definition152 dtime%second = rdt153 CALL xios_set_timestep(dtime)154 CALL xios_close_context_definition()155 156 CALL xios_update_calendar(0)157 158 DEALLOCATE( z_bnds )159 160 161 67 162 68 END SUBROUTINE iom_init … … 170 76 !!--------------------------------------------------------------------- 171 77 CHARACTER(len=*), INTENT(in) :: cdname 172 173 TYPE(xios_context) :: nemo_hdl174 175 IF( TRIM(Agrif_CFixed()) == '0' ) THEN176 CALL xios_get_handle(TRIM(cdname),nemo_hdl)177 ELSE178 CALL xios_get_handle(TRIM(Agrif_CFixed())//"_"//TRIM(cdname),nemo_hdl)179 ENDIF180 !181 CALL xios_set_current_context(nemo_hdl)182 183 78 ! 184 79 END SUBROUTINE iom_swap … … 201 96 CHARACTER(LEN=256) :: clname ! the name of the file based on cdname [[+clcpu]+clcpu] 202 97 CHARACTER(LEN=256) :: cltmpn ! tempory name to store clname (in writting mode) 203 CHARACTER(LEN=10) :: clsuffix ! ".nc" 98 CHARACTER(LEN=10) :: clsuffix ! ".nc" or ".dimg" 204 99 CHARACTER(LEN=15) :: clcpu ! the cpu number (max jpmax_digits digits) 205 100 CHARACTER(LEN=256) :: clinfo ! info character … … 266 161 CASE (jpnf90 ) ; clsuffix = '.nc' 267 162 CASE DEFAULT ; clsuffix = '' 268 CALL ctl_stop( TRIM(clinfo), 'accepted IO library is only jpnf90 (jpioipsl option has been removed) ' )269 163 END SELECT 270 164 ! Add the suffix if needed … … 279 173 IF( .NOT.llok ) THEN 280 174 ! we try to add the cpu number to the name 281 WRITE(clcpu,*) narea-1 282 175 WRITE(clcpu,*) narea-1 283 176 clcpu = TRIM(ADJUSTL(clcpu)) 284 177 iln = INDEX(clname,TRIM(clsuffix), back = .TRUE.) … … 327 220 END SELECT 328 221 ENDIF 329 ! Open the NetCDF file222 ! Open the NetCDF or RSTDIMG file 330 223 ! ============= 331 224 ! do we have some free file identifier? … … 353 246 CASE (jpnf90 ) ; CALL iom_nf90_open( clname, kiomid, llwrt, llok, idompar ) 354 247 CASE DEFAULT 355 CALL ctl_stop( TRIM(clinfo)//' accepted IO library is only jpnf90 (jpioipsl option has been removed) ' )356 248 END SELECT 357 249 ENDIF … … 390 282 CASE (jpnf90 ) ; CALL iom_nf90_close( jf ) 391 283 CASE DEFAULT 392 CALL ctl_stop( TRIM(clinfo)//' accepted IO library is only jpnf90 (jpioipsl option has been removed)' )393 284 END SELECT 394 285 iom_file(jf)%nfid = 0 ! free the id … … 446 337 SELECT CASE (iom_file(kiomid)%iolib) 447 338 CASE (jpnf90 ) ; iom_varid = iom_nf90_varid ( kiomid, cdvar, iiv, kdimsz, kndims ) 448 CASE DEFAULT 449 CALL ctl_stop( TRIM(clinfo)//' accepted IO library is only jpnf90 (jpioipsl option has been removed)' ) 339 CASE DEFAULT 450 340 END SELECT 451 341 ELSE … … 506 396 SELECT CASE (iom_file(kiomid)%iolib) 507 397 CASE (jpnf90 ) ; CALL iom_nf90_get( kiomid, idvar, pvar, itime ) 508 CASE DEFAULT 509 CALL ctl_stop( 'iom_g0d: accepted IO library is only jpnf90 (jpioipsl option has been removed)' ) 398 CASE DEFAULT 510 399 END SELECT 511 400 ENDIF … … 617 506 CHARACTER(LEN=256) :: clname ! file name 618 507 CHARACTER(LEN=1) :: clrankpv, cldmspc ! 619 LOGICAL :: ll_depth_spec ! T => if kstart, kcount present then *only* use values for 3rd spatial dimension.620 508 !--------------------------------------------------------------------- 621 509 ! … … 630 518 IF( PRESENT(kcount) .AND. (.NOT. PRESENT(kstart)) ) CALL ctl_stop(trim(clinfo), 'kcount present needs kstart present') 631 519 IF( PRESENT(kstart) .AND. (.NOT. PRESENT(kcount)) ) CALL ctl_stop(trim(clinfo), 'kstart present needs kcount present') 632 IF( PRESENT(kstart) .AND. idom /= jpdom_unknown .AND. idom /= jpdom_autoglo_xy ) & 633 & CALL ctl_stop(trim(clinfo), 'kstart present needs kdom = jpdom_unknown or kdom = jpdom_autoglo_xy') 520 IF( PRESENT(kstart) .AND. idom /= jpdom_unknown ) CALL ctl_stop(trim(clinfo), 'kstart present needs kdom = jpdom_unknown') 634 521 635 522 luse_jattr = .false. … … 643 530 ! Ok 644 531 CASE DEFAULT 645 CALL ctl_stop( TRIM(clinfo)//' accepted IO library is only jpnf90 (jpioipsl option has been removed)' )646 532 END SELECT 647 533 ENDIF … … 661 547 ! update idom definition... 662 548 ! Identify the domain in case of jpdom_auto(glo/dta) definition 663 IF( idom == jpdom_autoglo_xy ) THEN664 ll_depth_spec = .TRUE.665 idom = jpdom_autoglo666 ELSE667 ll_depth_spec = .FALSE.668 ENDIF669 549 IF( idom == jpdom_autoglo .OR. idom == jpdom_autodta ) THEN 670 550 IF( idom == jpdom_autoglo ) THEN ; idom = jpdom_global … … 720 600 istart(idmspc+1) = itime 721 601 722 IF( PRESENT(kstart) .AND. .NOT. ll_depth_spec) THEN ; istart(1:idmspc) = kstart(1:idmspc) ; icnt(1:idmspc) = kcount(1:idmspc)602 IF( PRESENT(kstart) ) THEN ; istart(1:idmspc) = kstart(1:idmspc) ; icnt(1:idmspc) = kcount(1:idmspc) 723 603 ELSE 724 IF( idom == jpdom_unknown ) THEN 604 IF( idom == jpdom_unknown ) THEN ; icnt(1:idmspc) = idimsz(1:idmspc) 725 605 ELSE 726 606 IF( .NOT. PRESENT(pv_r1d) ) THEN ! not a 1D array … … 745 625 ENDIF 746 626 IF( PRESENT(pv_r3d) ) THEN 747 IF( idom == jpdom_data ) THEN ; icnt(3) = jpkdta 748 ELSE IF( ll_depth_spec .AND. PRESENT(kstart) ) THEN ; istart(3) = kstart(3); icnt(3) = kcount(3) 749 ELSE ; icnt(3) = jpk 627 IF( idom == jpdom_data ) THEN ; icnt(3) = jpkdta 628 ELSE ; icnt(3) = jpk 750 629 ENDIF 751 630 ENDIF … … 818 697 CASE (jpnf90 ) ; CALL iom_nf90_get( kiomid, idvar, inbdim, istart, icnt, ix1, ix2, iy1, iy2, & 819 698 & pv_r1d, pv_r2d, pv_r3d ) 820 CASE DEFAULT 821 CALL ctl_stop( TRIM(clinfo)//' accepted IO library is only jpnf90 (jpioipsl option has been removed)' ) 699 CASE DEFAULT 822 700 END SELECT 823 701 … … 845 723 IF( zofs /= 0. ) pv_r1d(:) = pv_r1d(:) + zofs 846 724 ELSEIF( PRESENT(pv_r2d) ) THEN 725 !CDIR COLLAPSE 847 726 IF( zscf /= 1.) pv_r2d(:,:) = pv_r2d(:,:) * zscf 727 !CDIR COLLAPSE 848 728 IF( zofs /= 0.) pv_r2d(:,:) = pv_r2d(:,:) + zofs 849 729 ELSEIF( PRESENT(pv_r3d) ) THEN 730 !CDIR COLLAPSE 850 731 IF( zscf /= 1.) pv_r3d(:,:,:) = pv_r3d(:,:,:) * zscf 732 !CDIR COLLAPSE 851 733 IF( zofs /= 0.) pv_r3d(:,:,:) = pv_r3d(:,:,:) + zofs 852 734 ENDIF … … 899 781 SELECT CASE (iom_file(kiomid)%iolib) 900 782 CASE (jpnf90 ) ; CALL iom_nf90_gettime( kiomid, idvar, ptime, cdunits, cdcalendar ) 901 CASE DEFAULT 902 CALL ctl_stop( TRIM(clinfo)//' accepted IO library is only jpnf90 (jpioipsl option has been removed)' ) 783 CASE DEFAULT 903 784 END SELECT 904 785 ELSE … … 932 813 SELECT CASE (iom_file(kiomid)%iolib) 933 814 CASE (jpnf90 ) ; CALL iom_nf90_getatt( kiomid, cdatt, pvar ) 934 CASE DEFAULT 935 CALL ctl_stop( 'iom_g0d_att: accepted IO library is only jpnf90' ) 815 CASE DEFAULT 936 816 END SELECT 937 817 ENDIF … … 956 836 SELECT CASE (iom_file(kiomid)%iolib) 957 837 CASE (jpnf90 ) ; CALL iom_nf90_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r0d = pvar ) 958 CASE DEFAULT 959 CALL ctl_stop( 'iom_rp0d: accepted IO library is only jpnf90 (jpioipsl option has been removed)' ) 838 CASE DEFAULT 960 839 END SELECT 961 840 ENDIF … … 976 855 SELECT CASE (iom_file(kiomid)%iolib) 977 856 CASE (jpnf90 ) ; CALL iom_nf90_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r1d = pvar ) 978 CASE DEFAULT 979 CALL ctl_stop( 'iom_rp1d: accepted IO library is only jpnf90 (jpioipsl option has been removed)' ) 857 CASE DEFAULT 980 858 END SELECT 981 859 ENDIF … … 996 874 SELECT CASE (iom_file(kiomid)%iolib) 997 875 CASE (jpnf90 ) ; CALL iom_nf90_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r2d = pvar ) 998 CASE DEFAULT 999 CALL ctl_stop( 'iom_rp2d: accepted IO library is only jpnf90 (jpioipsl option has been removed)' ) 876 CASE DEFAULT 1000 877 END SELECT 1001 878 ENDIF … … 1016 893 SELECT CASE (iom_file(kiomid)%iolib) 1017 894 CASE (jpnf90 ) ; CALL iom_nf90_rstput( kt, kwrite, kiomid, cdvar, ivid, ktype, pv_r3d = pvar ) 1018 CASE DEFAULT 1019 CALL ctl_stop( 'iom_rp3d: accepted IO library is only jpnf90 (jpioipsl option has been removed)' ) 895 CASE DEFAULT 1020 896 END SELECT 1021 897 ENDIF … … 1031 907 REAL(wp) , INTENT(in) :: pfield0d 1032 908 REAL(wp) , DIMENSION(jpi,jpj) :: zz ! masson 1033 1034 zz(:,:)=pfield0d 1035 CALL xios_send_field(cdname, zz) 1036 !CALL xios_send_field(cdname, (/pfield0d/)) 1037 1038 1039 909 IF( .FALSE. ) WRITE(numout,*) cdname, pfield0d ! useless test to avoid compilation warnings 1040 910 END SUBROUTINE iom_p0d 1041 911 … … 1043 913 CHARACTER(LEN=*) , INTENT(in) :: cdname 1044 914 REAL(wp), DIMENSION(:), INTENT(in) :: pfield1d 1045 1046 CALL xios_send_field( cdname, RESHAPE( (/pfield1d/), (/1,1,SIZE(pfield1d)/) ) ) 1047 1048 1049 915 IF( .FALSE. ) WRITE(numout,*) cdname, pfield1d ! useless test to avoid compilation warnings 1050 916 END SUBROUTINE iom_p1d 1051 917 … … 1053 919 CHARACTER(LEN=*) , INTENT(in) :: cdname 1054 920 REAL(wp), DIMENSION(:,:), INTENT(in) :: pfield2d 1055 1056 CALL xios_send_field(cdname, pfield2d) 1057 1058 1059 921 IF( .FALSE. ) WRITE(numout,*) cdname, pfield2d ! useless test to avoid compilation warnings 1060 922 END SUBROUTINE iom_p2d 1061 923 … … 1063 925 CHARACTER(LEN=*) , INTENT(in) :: cdname 1064 926 REAL(wp), DIMENSION(:,:,:), INTENT(in) :: pfield3d 1065 1066 CALL xios_send_field(cdname, pfield3d) 1067 1068 1069 927 IF( .FALSE. ) WRITE(numout,*) cdname, pfield3d ! useless test to avoid compilation warnings 1070 928 END SUBROUTINE iom_p3d 1071 929 !!---------------------------------------------------------------------- … … 1073 931 1074 932 1075 SUBROUTINE iom_set_domain_attr( cdid, ni_glo, nj_glo, ibegin, jbegin, ni, nj, zoom_ibegin, zoom_jbegin, zoom_ni, zoom_nj, &1076 & data_dim, data_ibegin, data_ni, data_jbegin, data_nj, lonvalue, latvalue, mask, &1077 & nvertex, bounds_lon, bounds_lat, area )1078 CHARACTER(LEN=*) , INTENT(in) :: cdid1079 INTEGER , OPTIONAL, INTENT(in) :: ni_glo, nj_glo, ibegin, jbegin, ni, nj1080 INTEGER , OPTIONAL, INTENT(in) :: data_dim, data_ibegin, data_ni, data_jbegin, data_nj1081 INTEGER , OPTIONAL, INTENT(in) :: zoom_ibegin, zoom_jbegin, zoom_ni, zoom_nj, nvertex1082 REAL(wp), DIMENSION(:) , OPTIONAL, INTENT(in) :: lonvalue, latvalue1083 REAL(wp), DIMENSION(:,:) , OPTIONAL, INTENT(in) :: bounds_lon, bounds_lat, area1084 LOGICAL, DIMENSION(:,:) , OPTIONAL, INTENT(in) :: mask1085 1086 IF ( xios_is_valid_domain (cdid) ) THEN1087 CALL xios_set_domain_attr ( cdid, ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, jbegin=jbegin, ni=ni, nj=nj, &1088 & data_dim=data_dim, data_ibegin=data_ibegin, data_ni=data_ni, data_jbegin=data_jbegin, data_nj=data_nj , &1089 & zoom_ibegin=zoom_ibegin, zoom_jbegin=zoom_jbegin, zoom_ni=zoom_ni, zoom_nj=zoom_nj, &1090 & lonvalue=lonvalue, latvalue=latvalue, mask=mask, nvertex=nvertex, bounds_lon=bounds_lon, &1091 & bounds_lat=bounds_lat, area=area )1092 ENDIF1093 1094 IF ( xios_is_valid_domaingroup(cdid) ) THEN1095 CALL xios_set_domaingroup_attr( cdid, ni_glo=ni_glo, nj_glo=nj_glo, ibegin=ibegin, jbegin=jbegin, ni=ni, nj=nj, &1096 & data_dim=data_dim, data_ibegin=data_ibegin, data_ni=data_ni, data_jbegin=data_jbegin, data_nj=data_nj , &1097 & zoom_ibegin=zoom_ibegin, zoom_jbegin=zoom_jbegin, zoom_ni=zoom_ni, zoom_nj=zoom_nj, &1098 & lonvalue=lonvalue, latvalue=latvalue, mask=mask, nvertex=nvertex, bounds_lon=bounds_lon, &1099 & bounds_lat=bounds_lat, area=area )1100 ENDIF1101 CALL xios_solve_inheritance()1102 1103 END SUBROUTINE iom_set_domain_attr1104 1105 1106 SUBROUTINE iom_set_axis_attr( cdid, paxis, bounds )1107 CHARACTER(LEN=*) , INTENT(in) :: cdid1108 REAL(wp), DIMENSION(:) , OPTIONAL, INTENT(in) :: paxis1109 REAL(wp), DIMENSION(:,:), OPTIONAL, INTENT(in) :: bounds1110 IF ( PRESENT(paxis) ) THEN1111 IF ( xios_is_valid_axis (cdid) ) CALL xios_set_axis_attr ( cdid, size=SIZE(paxis), value=paxis )1112 IF ( xios_is_valid_axisgroup(cdid) ) CALL xios_set_axisgroup_attr( cdid, size=SIZE(paxis), value=paxis )1113 ENDIF1114 IF ( xios_is_valid_axis (cdid) ) CALL xios_set_axis_attr ( cdid, bounds=bounds )1115 IF ( xios_is_valid_axisgroup(cdid) ) CALL xios_set_axisgroup_attr( cdid, bounds=bounds )1116 CALL xios_solve_inheritance()1117 END SUBROUTINE iom_set_axis_attr1118 1119 1120 SUBROUTINE iom_set_field_attr( cdid, freq_op, freq_offset )1121 CHARACTER(LEN=*) , INTENT(in) :: cdid1122 CHARACTER(LEN=*),OPTIONAL , INTENT(in) :: freq_op1123 CHARACTER(LEN=*),OPTIONAL , INTENT(in) :: freq_offset1124 IF ( xios_is_valid_field (cdid) ) CALL xios_set_field_attr &1125 & ( cdid, freq_op=freq_op, freq_offset=freq_offset )1126 IF ( xios_is_valid_fieldgroup(cdid) ) CALL xios_set_fieldgroup_attr &1127 & ( cdid, freq_op=freq_op, freq_offset=freq_offset )1128 CALL xios_solve_inheritance()1129 END SUBROUTINE iom_set_field_attr1130 1131 1132 SUBROUTINE iom_set_file_attr( cdid, name, name_suffix )1133 CHARACTER(LEN=*) , INTENT(in) :: cdid1134 CHARACTER(LEN=*),OPTIONAL , INTENT(in) :: name, name_suffix1135 IF ( xios_is_valid_file (cdid) ) CALL xios_set_file_attr ( cdid, name=name, name_suffix=name_suffix )1136 IF ( xios_is_valid_filegroup(cdid) ) CALL xios_set_filegroup_attr( cdid, name=name, name_suffix=name_suffix )1137 CALL xios_solve_inheritance()1138 END SUBROUTINE iom_set_file_attr1139 1140 1141 SUBROUTINE iom_get_file_attr( cdid, name, name_suffix, output_freq )1142 CHARACTER(LEN=*) , INTENT(in ) :: cdid1143 CHARACTER(LEN=*),OPTIONAL , INTENT(out) :: name, name_suffix, output_freq1144 LOGICAL :: llexist1,llexist2,llexist31145 !---------------------------------------------------------------------1146 IF( PRESENT( name ) ) name = '' ! default values1147 IF( PRESENT( name_suffix ) ) name_suffix = ''1148 IF( PRESENT( output_freq ) ) output_freq = ''1149 IF ( xios_is_valid_file (cdid) ) THEN1150 CALL xios_solve_inheritance()1151 CALL xios_is_defined_file_attr ( cdid, name = llexist1, name_suffix = llexist2, output_freq = llexist3)1152 IF(llexist1) CALL xios_get_file_attr ( cdid, name = name )1153 IF(llexist2) CALL xios_get_file_attr ( cdid, name_suffix = name_suffix )1154 IF(llexist3) CALL xios_get_file_attr ( cdid, output_freq = output_freq )1155 ENDIF1156 IF ( xios_is_valid_filegroup(cdid) ) THEN1157 CALL xios_solve_inheritance()1158 CALL xios_is_defined_filegroup_attr( cdid, name = llexist1, name_suffix = llexist2, output_freq = llexist3)1159 IF(llexist1) CALL xios_get_filegroup_attr( cdid, name = name )1160 IF(llexist2) CALL xios_get_filegroup_attr( cdid, name_suffix = name_suffix )1161 IF(llexist3) CALL xios_get_filegroup_attr( cdid, output_freq = output_freq )1162 ENDIF1163 END SUBROUTINE iom_get_file_attr1164 1165 1166 SUBROUTINE iom_set_grid_attr( cdid, mask )1167 CHARACTER(LEN=*) , INTENT(in) :: cdid1168 LOGICAL, DIMENSION(:,:,:), OPTIONAL, INTENT(in) :: mask1169 IF ( xios_is_valid_grid (cdid) ) CALL xios_set_grid_attr ( cdid, mask=mask )1170 IF ( xios_is_valid_gridgroup(cdid) ) CALL xios_set_gridgroup_attr( cdid, mask=mask )1171 CALL xios_solve_inheritance()1172 END SUBROUTINE iom_set_grid_attr1173 1174 933 SUBROUTINE iom_setkt( kt, cdname ) 1175 INTEGER , INTENT(in) 934 INTEGER , INTENT(in):: kt 1176 935 CHARACTER(LEN=*), INTENT(in) :: cdname 1177 ! 1178 CALL iom_swap( cdname ) ! swap to cdname context 1179 CALL xios_update_calendar(kt) 1180 IF( cdname /= TRIM(cxios_context) ) CALL iom_swap( TRIM(cxios_context) ) ! return back to nemo context 1181 ! 936 IF( .FALSE. ) WRITE(numout,*) kt, cdname ! useless test to avoid compilation warnings 1182 937 END SUBROUTINE iom_setkt 1183 938 1184 939 SUBROUTINE iom_context_finalize( cdname ) 1185 CHARACTER(LEN=*), INTENT(in) :: cdname 1186 ! 1187 IF( xios_is_valid_context(cdname) ) THEN 1188 CALL iom_swap( cdname ) ! swap to cdname context 1189 CALL xios_context_finalize() ! finalize the context 1190 IF( cdname /= TRIM(cxios_context) ) CALL iom_swap( TRIM(cxios_context) ) ! return back to nemo context 1191 ENDIF 1192 ! 940 CHARACTER(LEN=*), INTENT(in) :: cdname 941 IF( .FALSE. ) WRITE(numout,*) cdname ! useless test to avoid compilation warnings 1193 942 END SUBROUTINE iom_context_finalize 1194 1195 1196 SUBROUTINE set_grid( cdgrd, plon, plat )1197 !!----------------------------------------------------------------------1198 !! *** ROUTINE set_grid ***1199 !!1200 !! ** Purpose : define horizontal grids1201 !!1202 !!----------------------------------------------------------------------1203 CHARACTER(LEN=1) , INTENT(in) :: cdgrd1204 REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: plon1205 REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: plat1206 !1207 REAL(wp), DIMENSION(jpi,jpj,jpk) :: zmask1208 INTEGER :: ni,nj1209 1210 ni=nlei-nldi+1 ; nj=nlej-nldj+11211 1212 CALL iom_set_domain_attr("grid_"//cdgrd, ni_glo=jpiglo, nj_glo=jpjglo, ibegin=nimpp+nldi-1, jbegin=njmpp+nldj-1, ni=ni, nj=nj)1213 CALL iom_set_domain_attr("grid_"//cdgrd, data_dim=2, data_ibegin = 1-nldi, data_ni = jpi, data_jbegin = 1-nldj, data_nj = jpj)1214 CALL iom_set_domain_attr("grid_"//cdgrd, lonvalue = RESHAPE(plon(nldi:nlei, nldj:nlej),(/ ni*nj /)), &1215 & latvalue = RESHAPE(plat(nldi:nlei, nldj:nlej),(/ ni*nj /)))1216 1217 IF ( ln_mskland ) THEN1218 ! mask land points, keep values on coast line -> specific mask for U, V and W points1219 SELECT CASE ( cdgrd )1220 CASE('T') ; zmask(:,:,:) = tmask(:,:,:)1221 CASE('U') ; zmask(2:jpim1,:,:) = tmask(2:jpim1,:,:) + tmask(3:jpi,:,:) ; CALL lbc_lnk( zmask, 'U', 1. )1222 CASE('V') ; zmask(:,2:jpjm1,:) = tmask(:,2:jpjm1,:) + tmask(:,3:jpj,:) ; CALL lbc_lnk( zmask, 'V', 1. )1223 CASE('W') ; zmask(:,:,2:jpk ) = tmask(:,:,1:jpkm1) + tmask(:,:,2:jpk) ; zmask(:,:,1) = tmask(:,:,1)1224 END SELECT1225 !1226 CALL iom_set_domain_attr( "grid_"//cdgrd , mask = RESHAPE(zmask(nldi:nlei,nldj:nlej,1),(/ni,nj /)) /= 0. )1227 CALL iom_set_grid_attr ( "grid_"//cdgrd//"_3D", mask = RESHAPE(zmask(nldi:nlei,nldj:nlej,:),(/ni,nj,jpk/)) /= 0. )1228 ENDIF1229 1230 END SUBROUTINE set_grid1231 1232 1233 SUBROUTINE set_grid_bounds( cdgrd, plon_cnr, plat_cnr, plon_pnt, plat_pnt )1234 !!----------------------------------------------------------------------1235 !! *** ROUTINE set_grid_bounds ***1236 !!1237 !! ** Purpose : define horizontal grid corners1238 !!1239 !!----------------------------------------------------------------------1240 CHARACTER(LEN=1) , INTENT(in) :: cdgrd1241 !1242 REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: plon_cnr, plat_cnr ! Lat/lon coordinates of a contiguous vertex of cell (i,j)1243 REAL(wp), DIMENSION(jpi,jpj), OPTIONAL, INTENT(in) :: plon_pnt, plat_pnt ! Lat/lon coordinates of the point of cell (i,j)1244 !1245 REAL(wp), ALLOCATABLE, DIMENSION(:,:,:,:) :: z_bnds ! Lat/lon coordinates of the vertices of cell (i,j)1246 REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: z_fld ! Working array to determine where to rotate cells1247 REAL(wp), ALLOCATABLE, DIMENSION(:,:) :: z_rot ! Lat/lon working array for rotation of cells1248 !1249 INTEGER :: icnr, jcnr ! Offset such that the vertex coordinate (i+icnr,j+jcnr)1250 ! ! represents the bottom-left corner of cell (i,j)1251 INTEGER :: ji, jj, jn, ni, nj1252 1253 ALLOCATE( z_bnds(4,jpi,jpj,2), z_fld(jpi,jpj), z_rot(4,2) )1254 1255 ! Offset of coordinate representing bottom-left corner1256 SELECT CASE ( TRIM(cdgrd) )1257 CASE ('T', 'W')1258 icnr = -1 ; jcnr = -11259 CASE ('U')1260 icnr = 0 ; jcnr = -11261 CASE ('V')1262 icnr = -1 ; jcnr = 01263 END SELECT1264 1265 ni = nlei-nldi+1 ; nj = nlej-nldj+1 ! Dimensions of subdomain interior1266 1267 z_fld(:,:) = 1._wp1268 CALL lbc_lnk( z_fld, cdgrd, -1. ) ! Working array for location of northfold1269 1270 ! Cell vertices that can be defined1271 DO jj = 2, jpjm11272 DO ji = 2, jpim11273 z_bnds(1,ji,jj,1) = plat_cnr(ji+icnr, jj+jcnr ) ! Bottom-left1274 z_bnds(2,ji,jj,1) = plat_cnr(ji+icnr+1,jj+jcnr ) ! Bottom-right1275 z_bnds(3,ji,jj,1) = plat_cnr(ji+icnr+1,jj+jcnr+1) ! Top-right1276 z_bnds(4,ji,jj,1) = plat_cnr(ji+icnr, jj+jcnr+1) ! Top-left1277 z_bnds(1,ji,jj,2) = plon_cnr(ji+icnr, jj+jcnr ) ! Bottom-left1278 z_bnds(2,ji,jj,2) = plon_cnr(ji+icnr+1,jj+jcnr ) ! Bottom-right1279 z_bnds(3,ji,jj,2) = plon_cnr(ji+icnr+1,jj+jcnr+1) ! Top-right1280 z_bnds(4,ji,jj,2) = plon_cnr(ji+icnr, jj+jcnr+1) ! Top-left1281 END DO1282 END DO1283 1284 ! Cell vertices on boundries1285 DO jn = 1, 41286 CALL lbc_lnk( z_bnds(jn,:,:,1), cdgrd, 1., pval=999._wp )1287 CALL lbc_lnk( z_bnds(jn,:,:,2), cdgrd, 1., pval=999._wp )1288 END DO1289 1290 ! Zero-size cells at closed boundaries if cell points provided,1291 ! otherwise they are closed cells with unrealistic bounds1292 IF( PRESENT(plon_pnt) .AND. PRESENT(plat_pnt) ) THEN1293 IF( (nbondi == -1 .OR. nbondi == 2) .AND. .NOT. (jperio == 1 .OR. jperio == 4 .OR. jperio == 6) ) THEN1294 DO jn = 1, 4 ! (West or jpni = 1), closed E-W1295 z_bnds(jn,1,:,1) = plat_pnt(1,:) ; z_bnds(jn,1,:,2) = plon_pnt(1,:)1296 END DO1297 ENDIF1298 IF( (nbondi == 1 .OR. nbondi == 2) .AND. .NOT. (jperio == 1 .OR. jperio == 4 .OR. jperio == 6) ) THEN1299 DO jn = 1, 4 ! (East or jpni = 1), closed E-W1300 z_bnds(jn,nlci,:,1) = plat_pnt(nlci,:) ; z_bnds(jn,nlci,:,2) = plon_pnt(nlci,:)1301 END DO1302 ENDIF1303 IF( nbondj == -1 .OR. (nbondj == 2 .AND. jperio /= 2) ) THEN1304 DO jn = 1, 4 ! South or (jpnj = 1, not symmetric)1305 z_bnds(jn,:,1,1) = plat_pnt(:,1) ; z_bnds(jn,:,1,2) = plon_pnt(:,1)1306 END DO1307 ENDIF1308 IF( (nbondj == 1 .OR. nbondj == 2) .AND. jperio < 3 ) THEN1309 DO jn = 1, 4 ! (North or jpnj = 1), no north fold1310 z_bnds(jn,:,nlcj,1) = plat_pnt(:,nlcj) ; z_bnds(jn,:,nlcj,2) = plon_pnt(:,nlcj)1311 END DO1312 ENDIF1313 ENDIF1314 1315 ! Rotate cells at the north fold1316 IF( (nbondj == 1 .OR. nbondj == 2) .AND. jperio >= 3 ) THEN1317 DO jj = 1, jpj1318 DO ji = 1, jpi1319 IF( z_fld(ji,jj) == -1. ) THEN1320 z_rot(1,:) = z_bnds(3,ji,jj,:) ; z_rot(2,:) = z_bnds(4,ji,jj,:)1321 z_rot(3,:) = z_bnds(1,ji,jj,:) ; z_rot(4,:) = z_bnds(2,ji,jj,:)1322 z_bnds(:,ji,jj,:) = z_rot(:,:)1323 ENDIF1324 END DO1325 END DO1326 1327 ! Invert cells at the symmetric equator1328 ELSE IF( nbondj == 2 .AND. jperio == 2 ) THEN1329 DO ji = 1, jpi1330 z_rot(1:2,:) = z_bnds(3:4,ji,1,:)1331 z_rot(3:4,:) = z_bnds(1:2,ji,1,:)1332 z_bnds(:,ji,1,:) = z_rot(:,:)1333 END DO1334 ENDIF1335 1336 CALL iom_set_domain_attr("grid_"//cdgrd, bounds_lat = RESHAPE(z_bnds(:,nldi:nlei,nldj:nlej,1),(/ 4,ni*nj /)), &1337 bounds_lon = RESHAPE(z_bnds(:,nldi:nlei,nldj:nlej,2),(/ 4,ni*nj /)), nvertex=4 )1338 1339 DEALLOCATE( z_bnds, z_fld, z_rot )1340 1341 END SUBROUTINE set_grid_bounds1342 1343 1344 SUBROUTINE set_grid_znl( plat )1345 !!----------------------------------------------------------------------1346 !! *** ROUTINE set_grid_znl ***1347 !!1348 !! ** Purpose : define grids for zonal mean1349 !!1350 !!----------------------------------------------------------------------1351 REAL(wp), DIMENSION(jpi,jpj), INTENT(in) :: plat1352 !1353 REAL(wp), DIMENSION(:), ALLOCATABLE :: zlon1354 INTEGER :: ni,nj, ix, iy1355 1356 1357 ni=nlei-nldi+1 ; nj=nlej-nldj+1 ! define zonal mean domain (jpj*jpk)1358 ALLOCATE( zlon(ni*nj) ) ; zlon(:) = 0.1359 1360 CALL iom_set_domain_attr("gznl", ni_glo=jpiglo, nj_glo=jpjglo, ibegin=nimpp+nldi-1, jbegin=njmpp+nldj-1, ni=ni, nj=nj)1361 CALL iom_set_domain_attr("gznl", data_dim=2, data_ibegin = 1-nldi, data_ni = jpi, data_jbegin = 1-nldj, data_nj = jpj)1362 CALL iom_set_domain_attr("gznl", lonvalue = zlon, &1363 & latvalue = RESHAPE(plat(nldi:nlei, nldj:nlej),(/ ni*nj /)))1364 !1365 CALL dom_ngb( 180., 90., ix, iy, 'T' ) ! i-line that passes near the North Pole : Reference latitude (used in plots)1366 CALL iom_set_domain_attr ('ptr', zoom_ibegin=ix, zoom_nj=jpjglo)1367 CALL iom_update_file_name('ptr')1368 !1369 END SUBROUTINE set_grid_znl1370 1371 SUBROUTINE set_scalar1372 !!----------------------------------------------------------------------1373 !! *** ROUTINE set_scalar ***1374 !!1375 !! ** Purpose : define fake grids for scalar point1376 !!1377 !!----------------------------------------------------------------------1378 REAL(wp), DIMENSION(1) :: zz = 1.1379 !!----------------------------------------------------------------------1380 CALL iom_set_domain_attr('scalarpoint', ni_glo=jpnij, nj_glo=1, ibegin=narea, jbegin=1, ni=1, nj=1)1381 CALL iom_set_domain_attr('scalarpoint', data_dim=2, data_ibegin = 1, data_ni = 1, data_jbegin = 1, data_nj = 1)1382 1383 zz=REAL(narea,wp)1384 CALL iom_set_domain_attr('scalarpoint', lonvalue=zz, latvalue=zz)1385 1386 END SUBROUTINE set_scalar1387 1388 1389 SUBROUTINE set_xmlatt1390 !!----------------------------------------------------------------------1391 !! *** ROUTINE set_xmlatt ***1392 !!1393 !! ** Purpose : automatic definitions of some of the xml attributs...1394 !!1395 !!----------------------------------------------------------------------1396 CHARACTER(len=1),DIMENSION( 3) :: clgrd ! suffix name1397 CHARACTER(len=256) :: clsuff ! suffix name1398 CHARACTER(len=1) :: cl1 ! 1 character1399 CHARACTER(len=2) :: cl2 ! 2 characters1400 CHARACTER(len=3) :: cl3 ! 3 characters1401 INTEGER :: ji, jg ! loop counters1402 INTEGER :: ix, iy ! i-,j- index1403 REAL(wp) ,DIMENSION(11) :: zlontao ! longitudes of tao moorings1404 REAL(wp) ,DIMENSION( 7) :: zlattao ! latitudes of tao moorings1405 REAL(wp) ,DIMENSION( 4) :: zlonrama ! longitudes of rama moorings1406 REAL(wp) ,DIMENSION(11) :: zlatrama ! latitudes of rama moorings1407 REAL(wp) ,DIMENSION( 3) :: zlonpira ! longitudes of pirata moorings1408 REAL(wp) ,DIMENSION( 9) :: zlatpira ! latitudes of pirata moorings1409 !!----------------------------------------------------------------------1410 !1411 ! frequency of the call of iom_put (attribut: freq_op)1412 WRITE(cl1,'(i1)') 1 ; CALL iom_set_field_attr('field_definition', freq_op = cl1//'ts', freq_offset='0ts')1413 1414 ! output file names (attribut: name)1415 DO ji = 1, 91416 WRITE(cl1,'(i1)') ji1417 CALL iom_update_file_name('file'//cl1)1418 END DO1419 DO ji = 1, 991420 WRITE(cl2,'(i2.2)') ji1421 CALL iom_update_file_name('file'//cl2)1422 END DO1423 DO ji = 1, 9991424 WRITE(cl3,'(i3.3)') ji1425 CALL iom_update_file_name('file'//cl3)1426 END DO1427 1428 ! Zooms...1429 clgrd = (/ 'T', 'U', 'W' /)1430 DO jg = 1, SIZE(clgrd) ! grid type1431 cl1 = clgrd(jg)1432 ! Equatorial section (attributs: jbegin, ni, name_suffix)1433 CALL dom_ngb( 0., 0., ix, iy, cl1 )1434 CALL iom_set_domain_attr ('Eq'//cl1, zoom_jbegin=iy, zoom_ni=jpiglo)1435 CALL iom_get_file_attr ('Eq'//cl1, name_suffix = clsuff )1436 CALL iom_set_file_attr ('Eq'//cl1, name_suffix = TRIM(clsuff)//'_Eq')1437 CALL iom_update_file_name('Eq'//cl1)1438 END DO1439 ! TAO moorings (attributs: ibegin, jbegin, name_suffix)1440 zlontao = (/ 137.0, 147.0, 156.0, 165.0, -180.0, -170.0, -155.0, -140.0, -125.0, -110.0, -95.0 /)1441 zlattao = (/ -8.0, -5.0, -2.0, 0.0, 2.0, 5.0, 8.0 /)1442 CALL set_mooring( zlontao, zlattao )1443 ! RAMA moorings (attributs: ibegin, jbegin, name_suffix)1444 zlonrama = (/ 55.0, 67.0, 80.5, 90.0 /)1445 zlatrama = (/ -16.0, -12.0, -8.0, -4.0, -1.5, 0.0, 1.5, 4.0, 8.0, 12.0, 15.0 /)1446 CALL set_mooring( zlonrama, zlatrama )1447 ! PIRATA moorings (attributs: ibegin, jbegin, name_suffix)1448 zlonpira = (/ -38.0, -23.0, -10.0 /)1449 zlatpira = (/ -19.0, -14.0, -8.0, 0.0, 4.0, 8.0, 12.0, 15.0, 20.0 /)1450 CALL set_mooring( zlonpira, zlatpira )1451 1452 1453 END SUBROUTINE set_xmlatt1454 1455 1456 SUBROUTINE set_mooring( plon, plat)1457 !!----------------------------------------------------------------------1458 !! *** ROUTINE set_mooring ***1459 !!1460 !! ** Purpose : automatic definitions of moorings xml attributs...1461 !!1462 !!----------------------------------------------------------------------1463 REAL(wp), DIMENSION(:), INTENT(in) :: plon, plat ! longitudes/latitudes oft the mooring1464 !1465 !!$ CHARACTER(len=1),DIMENSION(4) :: clgrd = (/ 'T', 'U', 'V', 'W' /) ! suffix name1466 CHARACTER(len=1),DIMENSION(1) :: clgrd = (/ 'T' /) ! suffix name1467 CHARACTER(len=256) :: clname ! file name1468 CHARACTER(len=256) :: clsuff ! suffix name1469 CHARACTER(len=1) :: cl1 ! 1 character1470 CHARACTER(len=6) :: clon,clat ! name of longitude, latitude1471 INTEGER :: ji, jj, jg ! loop counters1472 INTEGER :: ix, iy ! i-,j- index1473 REAL(wp) :: zlon, zlat1474 !!----------------------------------------------------------------------1475 DO jg = 1, SIZE(clgrd)1476 cl1 = clgrd(jg)1477 DO ji = 1, SIZE(plon)1478 DO jj = 1, SIZE(plat)1479 zlon = plon(ji)1480 zlat = plat(jj)1481 ! modifications for RAMA moorings1482 IF( zlon == 67. .AND. zlat == 15. ) zlon = 65.1483 IF( zlon == 90. .AND. zlat <= -4. ) zlon = 95.1484 IF( zlon == 95. .AND. zlat == -4. ) zlat = -5.1485 ! modifications for PIRATA moorings1486 IF( zlon == -38. .AND. zlat == -19. ) zlon = -34.1487 IF( zlon == -38. .AND. zlat == -14. ) zlon = -32.1488 IF( zlon == -38. .AND. zlat == -8. ) zlon = -30.1489 IF( zlon == -38. .AND. zlat == 0. ) zlon = -35.1490 IF( zlon == -23. .AND. zlat == 20. ) zlat = 21.1491 IF( zlon == -10. .AND. zlat == -14. ) zlat = -10.1492 IF( zlon == -10. .AND. zlat == -8. ) zlat = -6.1493 IF( zlon == -10. .AND. zlat == 4. ) THEN ; zlon = 0. ; zlat = 0. ; ENDIF1494 CALL dom_ngb( zlon, zlat, ix, iy, cl1 )1495 IF( zlon >= 0. ) THEN1496 IF( zlon == REAL(NINT(zlon), wp) ) THEN ; WRITE(clon, '(i3, a)') NINT( zlon), 'e'1497 ELSE ; WRITE(clon, '(f5.1,a)') zlon , 'e'1498 ENDIF1499 ELSE1500 IF( zlon == REAL(NINT(zlon), wp) ) THEN ; WRITE(clon, '(i3, a)') NINT(-zlon), 'w'1501 ELSE ; WRITE(clon, '(f5.1,a)') -zlon , 'w'1502 ENDIF1503 ENDIF1504 IF( zlat >= 0. ) THEN1505 IF( zlat == REAL(NINT(zlat), wp) ) THEN ; WRITE(clat, '(i2, a)') NINT( zlat), 'n'1506 ELSE ; WRITE(clat, '(f4.1,a)') zlat , 'n'1507 ENDIF1508 ELSE1509 IF( zlat == REAL(NINT(zlat), wp) ) THEN ; WRITE(clat, '(i2, a)') NINT(-zlat), 's'1510 ELSE ; WRITE(clat, '(f4.1,a)') -zlat , 's'1511 ENDIF1512 ENDIF1513 clname = TRIM(ADJUSTL(clat))//TRIM(ADJUSTL(clon))1514 CALL iom_set_domain_attr (TRIM(clname)//cl1, zoom_ibegin= ix, zoom_jbegin= iy)1515 CALL iom_get_file_attr (TRIM(clname)//cl1, name_suffix = clsuff )1516 CALL iom_set_file_attr (TRIM(clname)//cl1, name_suffix = TRIM(clsuff)//'_'//TRIM(clname))1517 CALL iom_update_file_name(TRIM(clname)//cl1)1518 END DO1519 END DO1520 END DO1521 1522 END SUBROUTINE set_mooring1523 1524 1525 SUBROUTINE iom_update_file_name( cdid )1526 !!----------------------------------------------------------------------1527 !! *** ROUTINE iom_update_file_name ***1528 !!1529 !! ** Purpose :1530 !!1531 !!----------------------------------------------------------------------1532 CHARACTER(LEN=*) , INTENT(in) :: cdid1533 !1534 CHARACTER(LEN=256) :: clname1535 CHARACTER(LEN=20) :: clfreq1536 CHARACTER(LEN=20) :: cldate1537 INTEGER :: idx1538 INTEGER :: jn1539 INTEGER :: itrlen1540 INTEGER :: iyear, imonth, iday, isec1541 REAL(wp) :: zsec1542 LOGICAL :: llexist1543 !!----------------------------------------------------------------------1544 1545 DO jn = 1,21546 1547 IF( jn == 1 ) CALL iom_get_file_attr( cdid, name = clname, output_freq = clfreq )1548 IF( jn == 2 ) CALL iom_get_file_attr( cdid, name_suffix = clname )1549 1550 IF ( TRIM(clname) /= '' ) THEN1551 1552 idx = INDEX(clname,'@expname@') + INDEX(clname,'@EXPNAME@')1553 DO WHILE ( idx /= 0 )1554 clname = clname(1:idx-1)//TRIM(cexper)//clname(idx+9:LEN_TRIM(clname))1555 idx = INDEX(clname,'@expname@') + INDEX(clname,'@EXPNAME@')1556 END DO1557 1558 idx = INDEX(clname,'@freq@') + INDEX(clname,'@FREQ@')1559 DO WHILE ( idx /= 0 )1560 IF ( TRIM(clfreq) /= '' ) THEN1561 itrlen = LEN_TRIM(clfreq)1562 IF ( clfreq(itrlen-1:itrlen) == 'mo' ) clfreq = clfreq(1:itrlen-1)1563 clname = clname(1:idx-1)//TRIM(clfreq)//clname(idx+6:LEN_TRIM(clname))1564 ELSE1565 CALL ctl_stop('error in the name of file id '//TRIM(cdid), &1566 & ' attribute output_freq is undefined -> cannot replace @freq@ in '//TRIM(clname) )1567 ENDIF1568 idx = INDEX(clname,'@freq@') + INDEX(clname,'@FREQ@')1569 END DO1570 1571 idx = INDEX(clname,'@startdate@') + INDEX(clname,'@STARTDATE@')1572 DO WHILE ( idx /= 0 )1573 cldate = iom_sdate( fjulday - rdt / rday )1574 clname = clname(1:idx-1)//TRIM(cldate)//clname(idx+11:LEN_TRIM(clname))1575 idx = INDEX(clname,'@startdate@') + INDEX(clname,'@STARTDATE@')1576 END DO1577 1578 idx = INDEX(clname,'@startdatefull@') + INDEX(clname,'@STARTDATEFULL@')1579 DO WHILE ( idx /= 0 )1580 cldate = iom_sdate( fjulday - rdt / rday, ldfull = .TRUE. )1581 clname = clname(1:idx-1)//TRIM(cldate)//clname(idx+15:LEN_TRIM(clname))1582 idx = INDEX(clname,'@startdatefull@') + INDEX(clname,'@STARTDATEFULL@')1583 END DO1584 1585 idx = INDEX(clname,'@enddate@') + INDEX(clname,'@ENDDATE@')1586 DO WHILE ( idx /= 0 )1587 cldate = iom_sdate( fjulday + rdt / rday * REAL( nitend - nit000, wp ), ld24 = .TRUE. )1588 clname = clname(1:idx-1)//TRIM(cldate)//clname(idx+9:LEN_TRIM(clname))1589 idx = INDEX(clname,'@enddate@') + INDEX(clname,'@ENDDATE@')1590 END DO1591 1592 idx = INDEX(clname,'@enddatefull@') + INDEX(clname,'@ENDDATEFULL@')1593 DO WHILE ( idx /= 0 )1594 cldate = iom_sdate( fjulday + rdt / rday * REAL( nitend - nit000, wp ), ld24 = .TRUE., ldfull = .TRUE. )1595 clname = clname(1:idx-1)//TRIM(cldate)//clname(idx+13:LEN_TRIM(clname))1596 idx = INDEX(clname,'@enddatefull@') + INDEX(clname,'@ENDDATEFULL@')1597 END DO1598 1599 IF( jn == 1 .AND. TRIM(Agrif_CFixed()) /= '0' ) clname = TRIM(Agrif_CFixed())//"_"//TRIM(clname)1600 IF( jn == 1 ) CALL iom_set_file_attr( cdid, name = clname )1601 IF( jn == 2 ) CALL iom_set_file_attr( cdid, name_suffix = clname )1602 1603 ENDIF1604 1605 END DO1606 1607 END SUBROUTINE iom_update_file_name1608 1609 1610 FUNCTION iom_sdate( pjday, ld24, ldfull )1611 !!----------------------------------------------------------------------1612 !! *** ROUTINE iom_sdate ***1613 !!1614 !! ** Purpose : send back the date corresponding to the given julian day1615 !!1616 !!----------------------------------------------------------------------1617 REAL(wp), INTENT(in ) :: pjday ! julian day1618 LOGICAL , INTENT(in ), OPTIONAL :: ld24 ! true to force 24:00 instead of 00:001619 LOGICAL , INTENT(in ), OPTIONAL :: ldfull ! true to get the compleate date: yyyymmdd_hh:mm:ss1620 !1621 CHARACTER(LEN=20) :: iom_sdate1622 CHARACTER(LEN=50) :: clfmt ! format used to write the date1623 INTEGER :: iyear, imonth, iday, ihour, iminute, isec1624 REAL(wp) :: zsec1625 LOGICAL :: ll24, llfull1626 !1627 IF( PRESENT(ld24) ) THEN ; ll24 = ld241628 ELSE ; ll24 = .FALSE.1629 ENDIF1630 1631 IF( PRESENT(ldfull) ) THEN ; llfull = ldfull1632 ELSE ; llfull = .FALSE.1633 ENDIF1634 1635 CALL ju2ymds( pjday, iyear, imonth, iday, zsec )1636 isec = NINT(zsec)1637 1638 IF ( ll24 .AND. isec == 0 ) THEN ! 00:00 of the next day -> move to 24:00 of the current day1639 CALL ju2ymds( pjday - 1., iyear, imonth, iday, zsec )1640 isec = 864001641 ENDIF1642 1643 IF( iyear < 10000 ) THEN ; clfmt = "i4.4,2i2.2" ! format used to write the date1644 ELSE ; WRITE(clfmt, "('i',i1,',2i2.2')") INT(LOG10(REAL(iyear,wp))) + 11645 ENDIF1646 1647 !$AGRIF_DO_NOT_TREAT1648 ! Should be fixed in the conv1649 IF( llfull ) THEN1650 clfmt = TRIM(clfmt)//",'_',i2.2,':',i2.2,':',i2.2"1651 ihour = isec / 36001652 isec = MOD(isec, 3600)1653 iminute = isec / 601654 isec = MOD(isec, 60)1655 WRITE(iom_sdate, '('//TRIM(clfmt)//')') iyear, imonth, iday, ihour, iminute, isec ! date of the end of run1656 ELSE1657 WRITE(iom_sdate, '('//TRIM(clfmt)//')') iyear, imonth, iday ! date of the end of run1658 ENDIF1659 !$AGRIF_END_DO_NOT_TREAT1660 1661 END FUNCTION iom_sdate1662 943 1663 944 1664 945 LOGICAL FUNCTION iom_use( cdname ) 1665 946 CHARACTER(LEN=*), INTENT(in) :: cdname 1666 iom_use = xios_field_is_active( cdname )947 iom_use = .FALSE. 1667 948 END FUNCTION iom_use 1668 949 -
branches/2017/dev_merge_2017/NEMOGCM/TOOLS/DOMAINcfg/src/nemogcm.f90
r7200 r9079 52 52 USE lib_mpp ! distributed memory computing 53 53 54 USE xios ! xIOserver55 56 54 USE lbcnfd , ONLY : isendto, nsndto, nfsloop, nfeloop ! Setup of north fold exchanges 57 55 … … 112 110 CALL nemo_closefile 113 111 ! 114 CALL xios_finalize ! end mpp communications with xios115 112 ! 116 113 END SUBROUTINE nemo_gcm … … 137 134 ! 138 135 cltxt = '' 139 cxios_context = 'nemo'140 136 ! 141 137 ! ! Open reference namelist and configuration namelist files … … 167 163 ! ! on unit number numond on first proc ! 168 164 ! !--------------------------------------------! 169 IF( Agrif_Root() ) THEN170 CALL xios_initialize( "for_xios_mpi_id",return_comm=ilocal_comm ) ! nemo local communicator given by xios171 ENDIF172 165 ! Nodes selection (control print return in cltxt) 173 narea = mynode( cltxt, 'output.namelist.dyn', numnam_ref, numnam_cfg, numond , nstop, ilocal_comm ) 166 ilocal_comm = 0 167 narea = mynode( cltxt, 'output.namelist.dyn', numnam_ref, numnam_cfg, numond , nstop ) 174 168 narea = narea + 1 ! mynode return the rank of proc (0 --> jpnij -1 ) 175 169 -
branches/2017/dev_merge_2017/NEMOGCM/TOOLS/DOMAINcfg/src/step_oce.f90
r6951 r9079 22 22 23 23 24 USE xios25 24 26 25 !!----------------------------------------------------------------------
Note: See TracChangeset
for help on using the changeset viewer.