- Timestamp:
- 07/17/08 12:27:56 (15 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
IOIPSL/trunk/src/histcom.f90
r295 r358 61 61 !- 62 62 INTERFACE histbeg 63 !! MODULE PROCEDURE histbeg_regular,histbeg_irregular64 63 MODULE PROCEDURE histbeg_totreg,histbeg_regular,histbeg_irregular 65 64 END INTERFACE … … 85 84 !- 86 85 INTEGER,SAVE :: nb_files=0 87 INTEGER,DIMENSION(nb_files_max),SAVE :: nb_var=0, 86 INTEGER,DIMENSION(nb_files_max),SAVE :: nb_var=0,nb_tax=0 88 87 !- 89 88 ! DOMAIN IDs for files … … 316 315 INTEGER,INTENT(IN) :: pim,pjm 317 316 REAL,DIMENSION(pim,pjm),INTENT(IN) :: plon,plat 318 INTEGER,INTENT(IN):: par_orix, par_szx, par_oriy,par_szy317 INTEGER,INTENT(IN):: par_orix,par_szx,par_oriy,par_szy 319 318 INTEGER,INTENT(IN) :: pitau0 320 REAL,INTENT(IN) :: pdate0, 321 INTEGER,INTENT(OUT) :: pfileid, 319 REAL,INTENT(IN) :: pdate0,pdeltat 320 INTEGER,INTENT(OUT) :: pfileid,phoriid 322 321 LOGICAL,INTENT(IN),OPTIONAL :: opt_rectilinear 323 322 INTEGER,INTENT(IN),OPTIONAL :: domain_id 324 323 !- 325 INTEGER :: ncid, 324 INTEGER :: ncid,iret 326 325 CHARACTER(LEN=120) :: file 327 326 CHARACTER(LEN=30) :: timenow … … 354 353 CALL ipslerr (3,"histbeg", & 355 354 & 'Table of files too small. You should increase nb_files_max', & 356 & 'in M_HISTCOM.f90 in order to accomodate all these files', ' ')355 & 'in histcom.f90 in order to accomodate all these files', ' ') 357 356 ENDIF 358 357 !- … … 371 370 ! Add DOMAIN number and ".nc" suffix in file name if needed 372 371 !- 373 file 372 file = pfilename 374 373 CALL flio_dom_file (file,domain_id) 375 374 !- 376 iret = NF90_CREATE (file, NF90_CLOBBER,ncid)375 iret = NF90_CREATE (file,NF90_CLOBBER,ncid) 377 376 !- 378 377 IF (rectilinear) THEN … … 390 389 ! 4.3 Global attributes 391 390 !- 392 iret = NF90_PUT_ATT (ncid,NF90_GLOBAL,'Conventions','CF-1. 1')391 iret = NF90_PUT_ATT (ncid,NF90_GLOBAL,'Conventions','CF-1.3') 393 392 iret = NF90_PUT_ATT (ncid,NF90_GLOBAL,'file_name',TRIM(file)) 394 393 iret = NF90_PUT_ATT (ncid,NF90_GLOBAL,'production',TRIM(model_name)) … … 409 408 ! 6.0 storing the geographical coordinates 410 409 !- 411 IF ( (pim /= par_szx).OR.(pjm /= par_szy) ) zoom(pfileid)=.TRUE.410 zoom(pfileid) = (pim /= par_szx).OR.(pjm /= par_szy) 412 411 regular(pfileid)=.TRUE. 413 412 !- … … 468 467 REAL,DIMENSION(:,:),INTENT(IN) :: plon_bounds,plat_bounds 469 468 INTEGER,INTENT(IN) :: pitau0 470 REAL,INTENT(IN) :: pdate0, 471 INTEGER,INTENT(OUT) :: pfileid, 469 REAL,INTENT(IN) :: pdate0,pdeltat 470 INTEGER,INTENT(OUT) :: pfileid,phoriid 472 471 INTEGER,INTENT(IN),OPTIONAL :: domain_id 473 472 !- 474 INTEGER :: ncid, 473 INTEGER :: ncid,iret 475 474 CHARACTER(LEN=120) :: file 476 475 CHARACTER(LEN=30) :: timenow … … 496 495 CALL ipslerr (3,"histbeg", & 497 496 & 'Table of files too small. You should increase nb_files_max', & 498 & 'in M_HISTCOM.f90 in order to accomodate all these files',' ')497 & 'in histcom.f90 in order to accomodate all these files',' ') 499 498 ENDIF 500 499 !- … … 527 526 ! 4.3 Global attributes 528 527 !- 529 iret = NF90_PUT_ATT (ncid,NF90_GLOBAL,'Conventions','CF-1. 1')528 iret = NF90_PUT_ATT (ncid,NF90_GLOBAL,'Conventions','CF-1.3') 530 529 iret = NF90_PUT_ATT (ncid,NF90_GLOBAL,'file_name',TRIM(file)) 531 530 iret = NF90_PUT_ATT (ncid,NF90_GLOBAL,'production',TRIM(model_name)) … … 596 595 CHARACTER(LEN=80) :: tmp_title, tmp_name 597 596 INTEGER :: ndim 598 INTEGER,DIMENSION(2) :: dims (2)597 INTEGER,DIMENSION(2) :: dims 599 598 INTEGER :: nlonid, nlatid 600 599 INTEGER :: orix, oriy, par_szx, par_szy … … 715 714 ! Transfer the latitude 716 715 !- 717 IF ( rectilinear) THEN716 IF (rectilinear) THEN 718 717 iret = NF90_PUT_VAR (ncid,nlatid,plat(1,oriy:oriy+par_szy-1)) 719 718 ELSE … … 791 790 ncid = ncdf_ids(pfileid) 792 791 !- 793 IF ( SIZE(plon_bounds,DIM=1) == pim) THEN792 IF (SIZE(plon_bounds,DIM=1) == pim) THEN 794 793 nbbounds = SIZE(plon_bounds,DIM=2) 795 794 transp = .TRUE. 796 ELSEIF ( SIZE(plon_bounds,DIM=2) == pim) THEN795 ELSEIF (SIZE(plon_bounds,DIM=2) == pim) THEN 797 796 nbbounds = SIZE(plon_bounds,DIM=1) 798 797 transp = .FALSE. … … 913 912 END SUBROUTINE histhori_irregular 914 913 !=== 915 SUBROUTINE histvert (pfileid, pzaxname, pzaxtitle, &916 & pz axunit, pzsize, pzvalues, pzaxid,pdirect)914 SUBROUTINE histvert (pfileid,pzaxname,pzaxtitle,pzaxunit, & 915 & pzsize,pzvalues,pzaxid,pdirect) 917 916 !--------------------------------------------------------------------- 918 917 !- This subroutine defines a vertical axis and returns it s id. … … 926 925 !- pzaxname : Name of the vertical axis 927 926 !- pzaxtitle: title of the vertical axis 928 !- pzaxunit : Units of the vertical axis 927 !- pzaxunit : Units of the vertical axis (no units ih blank string) 929 928 !- pzsize : size of the vertical axis 930 929 !- pzvalues : Coordinate values of the vetical axis … … 948 947 CHARACTER(LEN=*),INTENT(IN),OPTIONAL :: pdirect 949 948 !- 950 INTEGER :: pos, iv, nb, zdimid, zaxid_tmp 951 CHARACTER(LEN=20) :: str20 952 CHARACTER(LEN=70) :: str70, str71, str72 949 INTEGER :: pos,iv,zdimid,zaxid_tmp 950 CHARACTER(LEN=70) :: str71 953 951 CHARACTER(LEN=80) :: str80 954 952 CHARACTER(LEN=20) :: direction … … 986 984 ENDIF 987 985 !- 988 IF ( 986 IF (nb_zax(pfileid)+1 > nb_zax_max) THEN 989 987 CALL ipslerr (3,"histvert", & 990 988 & 'Table of vertical axes too small. You should increase ',& 991 & 'nb_zax_max in M_HISTCOM.f90 in order to accomodate all ', &989 & 'nb_zax_max in histcom.f90 in order to accomodate all ', & 992 990 & 'these variables ') 993 991 ENDIF 994 992 !- 995 993 iv = nb_zax(pfileid) 996 IF ( iv > 1) THEN 997 str20 = pzaxname 998 nb = iv-1 999 CALL find_str (zax_name(pfileid,1:nb),str20,pos) 994 IF (iv > 1) THEN 995 CALL find_str (zax_name(pfileid,1:iv-1),pzaxname,pos) 1000 996 ELSE 1001 997 pos = 0 1002 998 ENDIF 1003 999 !- 1004 IF ( pos > 0) THEN 1005 str70 = "Vertical axis already exists" 1006 WRITE(str71,'("Check variable ",A," in file",I3)') str20,pfileid 1007 str72 = "Can also be a wrong file ID in another declaration" 1008 CALL ipslerr (3,"histvert", str70, str71, str72) 1000 IF (pos > 0) THEN 1001 WRITE(str71,'("Check variable ",A," in file",I3)') & 1002 & TRIM(pzaxname),pfileid 1003 CALL ipslerr (3,"histvert", & 1004 & "Vertical axis already exists",TRIM(str71), & 1005 & "Can also be a wrong file ID in another declaration") 1009 1006 ENDIF 1010 1007 !- … … 1022 1019 iret = NF90_DEF_VAR (ncid,pzaxname(1:leng),NF90_FLOAT, & 1023 1020 & zaxid_tmp,zdimid) 1024 !-1025 1021 iret = NF90_PUT_ATT (ncid,zdimid,'axis',"Z") 1026 1022 leng = MIN(LEN_TRIM(pzaxunit),20) 1027 iret = NF90_PUT_ATT (ncid,zdimid,'units',pzaxunit(1:leng)) 1023 IF (leng > 0) THEN 1024 iret = NF90_PUT_ATT (ncid,zdimid,'units',pzaxunit(1:leng)) 1025 ENDIF 1028 1026 iret = NF90_PUT_ATT (ncid,zdimid,'positive',TRIM(direction)) 1029 1027 iret = NF90_PUT_ATT (ncid,zdimid,'valid_min', & … … 1044 1042 !- 3.0 add the information to the common 1045 1043 !- 1046 IF ( 1044 IF (check) & 1047 1045 & WRITE(*,*) "histvert : 3.0 add the information to the common" 1048 1046 !- … … 1072 1070 !- pvarname : Name of the variable, short and easy to remember 1073 1071 !- ptitle : Full name of the variable 1074 !- punit : Units of the variable 1072 !- punit : Units of the variable (no units if blank string) 1075 1073 !- 1076 1074 !- The next 3 arguments give the size of that data … … 1116 1114 REAL,DIMENSION(2),OPTIONAL,INTENT(IN) :: var_range 1117 1115 !- 1118 INTEGER :: iv, i, nb1116 INTEGER :: iv,i 1119 1117 CHARACTER(LEN=70) :: str70, str71, str72 1120 1118 CHARACTER(LEN=20) :: tmp_name 1121 CHARACTER(LEN=20) :: str20 1122 CHARACTER(LEN=40) :: str40, tab_str40(nb_var_max) 1119 CHARACTER(LEN=40) :: str40 1123 1120 CHARACTER(LEN=10) :: str10 1124 1121 CHARACTER(LEN=80) :: tmp_str80 … … 1135 1132 iv = nb_var(pfileid) 1136 1133 !- 1137 IF ( 1134 IF (iv > nb_var_max) THEN 1138 1135 CALL ipslerr (3,"histdef", & 1139 1136 & 'Table of variables too small. You should increase nb_var_max',& 1140 & 'in M_HISTCOM.f90 in order to accomodate all these variables', &1137 & 'in histcom.f90 in order to accomodate all these variables', & 1141 1138 & ' ') 1142 1139 ENDIF … … 1148 1145 !- 1149 1146 IF (iv > 1) THEN 1150 str20 = pvarname 1151 nb = iv-1 1152 CALL find_str (name(pfileid,1:nb),str20,pos) 1147 CALL find_str (name(pfileid,1:iv-1),pvarname,pos) 1153 1148 ELSE 1154 1149 pos = 0 … … 1157 1152 IF (pos > 0) THEN 1158 1153 str70 = "Variable already exists" 1159 WRITE(str71,'("Check variable ",a," in file",I3)') str20,pfileid 1154 WRITE(str71,'("Check variable ",a," in file",I3)') & 1155 & TRIM(pvarname),pfileid 1160 1156 str72 = "Can also be a wrong file ID in another declaration" 1161 1157 CALL ipslerr (3,"histdef", str70, str71, str72) … … 1235 1231 ! and a fall back onto the default grid 1236 1232 !- 1237 IF ( phoriid > 0 .AND. phoriid <= nb_hax(pfileid)) THEN1233 IF ( (phoriid > 0).AND.(phoriid <= nb_hax(pfileid)) ) THEN 1238 1234 var_haxid(pfileid,iv) = phoriid 1239 1235 ELSE … … 1250 1246 !-- Does the vertical coordinate exist ? 1251 1247 !- 1252 IF ( 1248 IF (pzid > nb_zax(pfileid)) THEN 1253 1249 WRITE(str70, & 1254 1250 & '("The vertical coordinate chosen for variable ",a)') & … … 1261 1257 !- 1262 1258 IF (par_szz /= zax_size(pfileid,pzid)) THEN 1263 str20 = zax_name(pfileid,pzid)1264 1259 str70 = "The size of the zoom does not correspond "// & 1265 1260 & "to the size of the chosen vertical axis" 1266 1261 WRITE(str71,'("Size of zoom in z :", I4)') par_szz 1267 1262 WRITE(str72,'("Size declared for axis ",A," :",I4)') & 1268 & TRIM( str20),zax_size(pfileid,pzid)1263 & TRIM(zax_name(pfileid,pzid)),zax_size(pfileid,pzid) 1269 1264 CALL ipslerr (3,"histdef", str70, str71, str72) 1270 1265 ENDIF … … 1272 1267 !-- Is the zoom smaler that the total size of the variable ? 1273 1268 !- 1274 IF ( pzsize < par_szz ) THEN 1275 str20 = zax_name(pfileid,pzid) 1269 IF (pzsize < par_szz) THEN 1276 1270 str70 = "The vertical size of variable "// & 1277 1271 & "is smaller than that of the zoom." … … 1321 1315 !- 1322 1316 CALL ioget_calendar(un_an, un_jour) 1323 IF ( 1317 IF (pfreq_opp < 0) THEN 1324 1318 CALL ioget_calendar(un_an) 1325 1319 test_fopp = pfreq_opp*(-1.)*un_an/12.*un_jour … … 1327 1321 test_fopp = pfreq_opp 1328 1322 ENDIF 1329 IF ( 1323 IF (pfreq_wrt < 0) THEN 1330 1324 CALL ioget_calendar(un_an) 1331 1325 test_fwrt = pfreq_wrt*(-1.)*un_an/12.*un_jour … … 1370 1364 str72 = "PATCH : The smalest frequency of both is used" 1371 1365 CALL ipslerr (2,"histdef", str70, str71, str72) 1372 IF ( 1366 IF (test_fopp < test_fwrt) THEN 1373 1367 freq_opp(pfileid,iv) = pfreq_opp 1374 1368 freq_wrt(pfileid,iv) = pfreq_opp … … 1427 1421 IF (check) WRITE(*,*) "histdef : 6.0" 1428 1422 !- 1429 IF ( freq_wrt(pfileid,iv) > 0) THEN1423 IF (freq_wrt(pfileid,iv) > 0) THEN 1430 1424 WRITE(str10,'(I8.8)') INT(freq_wrt(pfileid,iv)) 1431 1425 str40 = TRIM(tmp_topp)//"_"//TRIM(str10) … … 1434 1428 str40 = TRIM(tmp_topp)//"_"//TRIM(str10) 1435 1429 ENDIF 1436 !- 1437 tab_str40(1:nb_tax(pfileid)) = tax_name(pfileid,1:nb_tax(pfileid)) 1438 CALL find_str (tab_str40(1:nb_tax(pfileid)),str40,pos) 1430 CALL find_str (tax_name(pfileid,1:nb_tax(pfileid)),str40,pos) 1439 1431 !- 1440 1432 ! No time axis for once, l_max, l_min or never operation … … 1444 1436 & .AND.(TRIM(tmp_topp) /= 'l_max') & 1445 1437 & .AND.(TRIM(tmp_topp) /= 'l_min') ) THEN 1446 IF ( 1438 IF (pos < 0) THEN 1447 1439 nb_tax(pfileid) = nb_tax(pfileid)+1 1448 1440 tax_name(pfileid,nb_tax(pfileid)) = str40 … … 1578 1570 ttitle = title(pfileid,iv) 1579 1571 !--- 1580 IF ( 1572 IF (regular(pfileid) ) THEN 1581 1573 dims(1:2) = (/ xid(pfileid), yid(pfileid) /) 1582 1574 dim_cnt = 2 … … 1591 1583 ! 2.1 dimension of field 1592 1584 !--- 1593 IF ( 1585 IF ((TRIM(tmp_opp) /= 'never')) THEN 1594 1586 IF ( (TRIM(tmp_opp) /= 'once') & 1595 1587 & .AND.(TRIM(tmp_opp) /= 'l_max') & … … 1617 1609 ncvar_ids(pfileid,iv) = ncvarid 1618 1610 !- 1619 iret = NF90_PUT_ATT (ncid,ncvarid,'units',TRIM(tunit)) 1611 IF (LEN_TRIM(tunit) > 0) THEN 1612 iret = NF90_PUT_ATT (ncid,ncvarid,'units',TRIM(tunit)) 1613 ENDIF 1620 1614 !- 1621 1615 iret = NF90_PUT_ATT (ncid,ncvarid,'missing_value', & … … 1651 1645 !- 1652 1646 IF (itax > 0) THEN 1653 IF ( 1647 IF (nb_tax(pfileid) > 1) THEN 1654 1648 str30 = "t_"//tax_name(pfileid,itax) 1655 1649 ELSE … … 1668 1662 & REAL(freq_wrt(pfileid,iv),KIND=4)) 1669 1663 ENDIF 1670 iret = NF90_PUT_ATT (ncid,ncvarid,' associate',TRIM(assoc))1664 iret = NF90_PUT_ATT (ncid,ncvarid,'coordinates',TRIM(assoc)) 1671 1665 ENDIF 1672 1666 ENDDO … … 1678 1672 ENDIF 1679 1673 !- 1680 ! 3.0 Put the netcdf file into wr te mode1674 ! 3.0 Put the netcdf file into write mode 1681 1675 !- 1682 1676 IF (check) WRITE(*,*) "histend : 3.0" … … 2199 2193 ALLOCATE (buff_tmp2(datasz_max(pfileid,varid))) 2200 2194 buff_tmp2_sz = datasz_max(pfileid,varid) 2201 ELSE IF ( 2195 ELSE IF (datasz_max(pfileid,varid) > buff_tmp2_sz) THEN 2202 2196 IF (check) THEN 2203 2197 WRITE(*,*) "histwrite_real 1.2 re-allocate buff_tmp2 : ", & … … 2218 2212 ! 3.1 DO the Operations only if needed 2219 2213 !- 2220 IF ( do_oper) THEN2214 IF (do_oper) THEN 2221 2215 i = pfileid 2222 2216 nbout = nbdpt … … 2305 2299 IF (check) WRITE(*,*) "histwrite: 6.0", pfileid 2306 2300 !- 2307 IF ( do_write) THEN2301 IF (do_write) THEN 2308 2302 !- 2309 2303 ncvarid = ncvar_ids(pfileid,varid) … … 2327 2321 IF (check) WRITE(*,*) "histwrite: 6.2", pfileid 2328 2322 !- 2329 itax = var_axid(pfileid, 2330 itime = nb_wrt(pfileid, 2323 itax = var_axid(pfileid,varid) 2324 itime = nb_wrt(pfileid,varid)+1 2331 2325 !- 2332 2326 IF (tax_last(pfileid, itax) < itime) THEN … … 2357 2351 ENDIF 2358 2352 ELSE 2359 IF ( regular(pfileid)) THEN2353 IF (regular(pfileid)) THEN 2360 2354 corner(1:4) = (/ 1, 1, 1, itime /) 2361 2355 edges(1:4) = (/ zsize(pfileid,varid,1), & … … 2417 2411 LOGICAL,SAVE :: learning(nb_files_max)=.TRUE. 2418 2412 INTEGER,SAVE :: overlap(nb_files_max) = -1 2419 INTEGER,SAVE :: varseq(nb_files_max, 2413 INTEGER,SAVE :: varseq(nb_files_max,nb_var_max*3) 2420 2414 INTEGER,SAVE :: varseq_len(nb_files_max) = 0 2421 2415 INTEGER,SAVE :: varseq_pos(nb_files_max) 2422 2416 INTEGER,SAVE :: varseq_err(nb_files_max) = 0 2423 INTEGER :: ib, nb, sp, nx, pos 2424 CHARACTER(LEN=20) :: str20 2417 INTEGER :: ib,sp,nx,pos 2425 2418 CHARACTER(LEN=70) :: str70 2426 2419 !- 2427 2420 LOGICAL :: check = .FALSE. 2428 2421 !--------------------------------------------------------------------- 2429 nb = nb_var(pfid)2430 !-2431 2422 IF (check) THEN 2432 2423 WRITE(*,*) 'histvar_seq, start of the subroutine :',learning(pfid) … … 2448 2439 !-- 1.1 Find the position of this string 2449 2440 !- 2450 str20 = pvarname 2451 CALL find_str (name(pfid,1:nb),str20,pos) 2452 !- 2441 CALL find_str (name(pfid,1:nb_var(pfid)),pvarname,pos) 2453 2442 IF (pos > 0) THEN 2454 2443 pvid = pos … … 2457 2446 & 'The name of the variable you gave has not been declared', & 2458 2447 & 'You should use subroutine histdef for declaring variable', & 2459 & TRIM( str20))2448 & TRIM(pvarname)) 2460 2449 ENDIF 2461 2450 !- … … 2463 2452 !-- in the sequence of calls 2464 2453 !- 2465 IF ( varseq_err(pfid) .GE. 0) THEN2454 IF (varseq_err(pfid) >= 0) THEN 2466 2455 sp = varseq_len(pfid)+1 2467 2456 IF (sp <= nb_var_max*3) THEN … … 2509 2498 IF (nx > varseq_len(pfid)) nx = 1 2510 2499 !- 2511 pvid = varseq(pfid, nx) 2512 !- 2513 IF ( TRIM(name(pfid,pvid)) /= TRIM(pvarname) ) THEN 2514 str20 = pvarname 2515 CALL find_str (name(pfid,1:nb),str20,pos) 2500 pvid = varseq(pfid,nx) 2501 !- 2502 IF (TRIM(name(pfid,pvid)) /= TRIM(pvarname)) THEN 2503 CALL find_str (name(pfid,1:nb_var(pfid)),pvarname,pos) 2516 2504 IF (pos > 0) THEN 2517 2505 pvid = pos … … 2519 2507 CALL ipslerr (3,"histvar_seq", & 2520 2508 & 'The name of the variable you gave has not been declared',& 2521 & 'You should use subroutine histdef for declaring variable',str20) 2509 & 'You should use subroutine histdef for declaring variable', & 2510 & TRIM(pvarname)) 2522 2511 ENDIF 2523 2512 varseq_err(pfid) = varseq_err(pfid)+1 … … 2577 2566 ENDIF 2578 2567 !- 2579 IF ( file_exists) THEN2568 IF (file_exists) THEN 2580 2569 IF (check) THEN 2581 2570 WRITE(*,*) 'Synchronising specified file number :', file … … 2624 2613 !-- 1. Loop on the number of variables to add some final information 2625 2614 !--- 2626 IF ( check) WRITE(*,*) 'Entering loop on vars :', nb_var(ifile)2615 IF (check) WRITE(*,*) 'Entering loop on vars :', nb_var(ifile) 2627 2616 DO iv=1,nb_var(ifile) 2628 2617 IF (hist_wrt_rng(ifile,iv)) THEN … … 2643 2632 ENDDO 2644 2633 !--- 2645 !-- 2. 0Close the file2634 !-- 2. Close the file 2646 2635 !--- 2647 IF (check) WRITE(*,*) 'close file :', 2636 IF (check) WRITE(*,*) 'close file :',ncid 2648 2637 iret = NF90_CLOSE (ncid) 2649 2638 IF (iret /= NF90_NOERR) THEN 2650 2639 WRITE(str70,'("This file has been already closed :",I3)') ifile 2651 CALL ipslerr (2,'histclo',str70,'',' 2640 CALL ipslerr (2,'histclo',str70,'','') 2652 2641 ENDIF 2653 2642 ENDDO
Note: See TracChangeset
for help on using the changeset viewer.