Changeset 1791 for LMDZ5/trunk
- Timestamp:
- Jul 17, 2013, 12:20:19 PM (11 years ago)
- Location:
- LMDZ5/trunk/libf/phylmd
- Files:
-
- 6 edited
Legend:
- Unmodified
- Added
- Removed
-
LMDZ5/trunk/libf/phylmd/aero_mod.F90
r1764 r1791 42 42 43 43 ! Corresponding names for the aerosols 44 CHARACTER(len=7),DIMENSION(naero_spc) :: name_aero=(/&44 CHARACTER(len=7),DIMENSION(naero_spc), PARAMETER :: name_aero=(/& 45 45 "ASBCM ", & 46 46 "ASPOMM ", & -
LMDZ5/trunk/libf/phylmd/iophy.F90
r1775 r1791 6 6 ! abd REAL,private,allocatable,dimension(:),save :: io_lat 7 7 ! abd REAL,private,allocatable,dimension(:),save :: io_lon 8 REAL,allocatable,dimension(:),save :: io_lat 9 REAL,allocatable,dimension(:),save :: io_lon 10 INTEGER, save :: phys_domain_id 11 INTEGER, save :: npstn 12 INTEGER, allocatable, dimension(:), save :: nptabij 8 REAL,ALLOCATABLE,DIMENSION(:),SAVE :: io_lat 9 REAL,ALLOCATABLE,DIMENSION(:),SAVE :: io_lon 10 INTEGER, SAVE :: phys_domain_id 11 INTEGER, SAVE :: npstn 12 INTEGER, ALLOCATABLE, DIMENSION(:), SAVE :: nptabij 13 INTEGER, SAVE :: itau_iophy 14 15 !$OMP THREADPRIVATE(itau_iophy) 13 16 14 17 INTERFACE histwrite_phy 15 MODULE PROCEDURE histwrite2d_phy,histwrite3d_phy 18 MODULE PROCEDURE histwrite2d_phy,histwrite3d_phy,histwrite2d_phy_old,histwrite3d_phy_old 16 19 END INTERFACE 17 20 … … 322 325 end subroutine histbeg_phy_points 323 326 324 subroutine histwrite2d_phy(nid,lpoint,name,itau,field) 325 USE dimphy 326 USE mod_phys_lmdz_para 327 SUBROUTINE histwrite2d_phy_old(nid,lpoint,name,itau,field) 328 USE dimphy 329 USE mod_phys_lmdz_para 330 USE phys_output_var_mod 327 331 USE ioipsl 328 implicit none332 IMPLICIT NONE 329 333 include 'dimensions.h' 330 334 include 'iniprint.h' … … 341 345 integer :: ip 342 346 real,allocatable,dimension(:) :: fieldok 347 343 348 344 349 IF (size(field)/=klon) CALL abort_gcm('iophy::histwrite2d','Field first dimension not equal to klon',1) … … 379 384 deallocate(index2d) 380 385 deallocate(fieldok) 381 !$OMP END MASTER 382 end subroutine histwrite2d_phy 383 384 subroutine histwrite3d_phy(nid,lpoint,name,itau,field) 385 USE dimphy 386 USE mod_phys_lmdz_para 386 !$OMP END MASTER 387 388 389 end subroutine histwrite2d_phy_old 390 391 subroutine histwrite3d_phy_old(nid,lpoint,name,itau,field) 392 USE dimphy 393 USE mod_phys_lmdz_para 394 USE phys_output_var_mod 387 395 388 396 use ioipsl … … 401 409 INTEGER, ALLOCATABLE, dimension(:) :: index3d 402 410 real,allocatable, dimension(:,:) :: fieldok 411 403 412 404 413 IF (size(field,1)/=klon) CALL abort_gcm('iophy::histwrite3d','Field first dimension not equal to klon',1) … … 450 459 deallocate(fieldok) 451 460 !$OMP END MASTER 452 end subroutine histwrite3d_phy 461 462 end subroutine histwrite3d_phy_old 463 464 465 ! ug NOUVELLE VERSION DES WRITE AVEC LA BOUCLE DO RENTREE 466 SUBROUTINE histwrite2d_phy(var,field, STD_iff) 467 USE dimphy 468 USE mod_phys_lmdz_para 469 USE ioipsl 470 !Pour avoir nfiles, nidfiles tout ça tout ça... 471 USE phys_output_var_mod 472 473 474 475 #ifdef CPP_XIOS 476 ! USE WXIOS 477 #endif 478 479 IMPLICIT NONE 480 include 'dimensions.h' 481 482 ! integer,intent(in) :: nid 483 ! logical,intent(in) :: lpoint 484 ! character*(*), intent(IN) :: name 485 ! integer, intent(in) :: itau 486 ! real,dimension(:),intent(in) :: field 487 488 TYPE(ctrl_out), INTENT(IN) :: var 489 REAL, DIMENSION(:), INTENT(IN) :: field 490 INTEGER, INTENT(IN), OPTIONAL :: STD_iff ! ug RUSTINE POUR LES STD LEVS..... 491 492 INTEGER :: iff, iff_beg, iff_end 493 494 REAL,dimension(klon_mpi) :: buffer_omp 495 INTEGER, allocatable, dimension(:) :: index2d 496 REAL :: Field2d(iim,jj_nb) 497 498 INTEGER :: ip 499 REAL, ALLOCATABLE, DIMENSION(:) :: fieldok 500 501 ! ug RUSTINE POUR LES STD LEVS..... 502 IF (PRESENT(STD_iff)) THEN 503 iff_beg = STD_iff 504 iff_end = STD_iff 505 ELSE 506 iff_beg = 1 507 iff_end = nfiles 508 END IF 509 510 IF (size(field)/=klon) CALL abort_gcm('iophy::histwrite2d','Field first dimension not equal to klon',1) 511 512 CALL Gather_omp(field,buffer_omp) 513 !$OMP MASTER 514 CALL grid1Dto2D_mpi(buffer_omp,Field2d) 515 516 ! La boucle sur les fichiers: 517 DO iff=iff_beg, iff_end 518 IF (var%flag(iff) <= lev_files(iff) .AND. clef_files(iff)) THEN 519 520 IF(.NOT.clef_stations(iff)) THEN 521 ALLOCATE(index2d(iim*jj_nb)) 522 ALLOCATE(fieldok(iim*jj_nb)) 523 524 CALL histwrite(nid_files(iff),var%name,itau_iophy,Field2d,iim*jj_nb,index2d) 525 #ifdef CPP_XIOS 526 ! IF (iff .EQ. 1) THEN 527 ! CALL wxios_write_2D(var%name, Field2d) 528 ! ENDIF 529 #endif 530 ELSE 531 ALLOCATE(fieldok(npstn)) 532 ALLOCATE(index2d(npstn)) 533 534 IF (is_sequential) THEN 535 ! klon_mpi_begin=1 536 ! klon_mpi_end=klon 537 DO ip=1, npstn 538 fieldok(ip)=buffer_omp(nptabij(ip)) 539 ENDDO 540 ELSE 541 DO ip=1, npstn 542 ! print*,'histwrite2d is_sequential npstn ip name nptabij',npstn,ip,name,nptabij(ip) 543 IF(nptabij(ip).GE.klon_mpi_begin.AND. & 544 nptabij(ip).LE.klon_mpi_end) THEN 545 fieldok(ip)=buffer_omp(nptabij(ip)-klon_mpi_begin+1) 546 ENDIF 547 ENDDO 548 ENDIF 549 550 CALL histwrite(nid_files(iff),var%name,itau_iophy,fieldok,npstn,index2d) 551 ENDIF 552 553 deallocate(index2d) 554 deallocate(fieldok) 555 ENDIF !levfiles 556 ENDDO 557 !$OMP END MASTER 558 559 END SUBROUTINE histwrite2d_phy 560 561 562 ! ug NOUVELLE VERSION DES WRITE AVEC LA BOUCLE DO RENTREE 563 SUBROUTINE histwrite3d_phy(var, field) 564 USE dimphy 565 USE mod_phys_lmdz_para 566 567 use ioipsl 568 !Pour avoir nfiles, nidfiles tout ça tout ça... 569 USE phys_output_var_mod 570 571 572 #ifdef CPP_XIOS 573 ! USE WXIOS 574 #endif 575 576 577 IMPLICIT NONE 578 include 'dimensions.h' 579 580 ! integer,intent(in) :: nid 581 ! logical,intent(in) :: lpoint 582 ! character*(*), intent(IN) :: name 583 ! integer, intent(in) :: itau 584 ! real,dimension(:,:),intent(in) :: field ! --> field(klon,:) 585 586 TYPE(ctrl_out), INTENT(IN) :: var 587 REAL, DIMENSION(:,:), INTENT(IN) :: field ! --> field(klon,:) 588 589 590 REAL,DIMENSION(klon_mpi,SIZE(field,2)) :: buffer_omp 591 REAL :: Field3d(iim,jj_nb,SIZE(field,2)) 592 INTEGER :: ip, n, nlev, iff 593 INTEGER, ALLOCATABLE, DIMENSION(:) :: index3d 594 REAL,ALLOCATABLE, DIMENSION(:,:) :: fieldok 595 596 IF (size(field,1)/=klon) CALL abort_gcm('iophy::histwrite3d','Field first dimension not equal to klon',1) 597 nlev=size(field,2) 598 599 ! print*,'hist3d_phy mpi_rank npstn=',mpi_rank,npstn 600 601 ! DO ip=1, npstn 602 ! print*,'hist3d_phy mpi_rank nptabij',mpi_rank,nptabij(ip) 603 ! ENDDO 604 605 CALL Gather_omp(field,buffer_omp) 606 !$OMP MASTER 607 CALL grid1Dto2D_mpi(buffer_omp,field3d) 608 609 610 ! BOUCLE SUR LES FICHIERS 611 DO iff=1, nfiles 612 IF (var%flag(iff) <= lev_files(iff) .AND. clef_files(iff)) THEN 613 IF (.NOT.clef_stations(iff)) THEN 614 ALLOCATE(index3d(iim*jj_nb*nlev)) 615 ALLOCATE(fieldok(iim*jj_nb,nlev)) 616 CALL histwrite(nid_files(iff),var%name,itau_iophy,Field3d,iim*jj_nb*nlev,index3d) 617 #ifdef CPP_XIOS 618 ! IF (iff .EQ. 1) THEN 619 ! CALL wxios_write_3D(var%name, Field3d(:,:,1:klev)) 620 ! ENDIF 621 #endif 622 623 ELSE 624 nlev=size(field,2) 625 ALLOCATE(index3d(npstn*nlev)) 626 ALLOCATE(fieldok(npstn,nlev)) 627 628 IF (is_sequential) THEN 629 ! klon_mpi_begin=1 630 ! klon_mpi_end=klon 631 DO n=1, nlev 632 DO ip=1, npstn 633 fieldok(ip,n)=buffer_omp(nptabij(ip),n) 634 ENDDO 635 ENDDO 636 ELSE 637 DO n=1, nlev 638 DO ip=1, npstn 639 IF(nptabij(ip).GE.klon_mpi_begin.AND. & 640 nptabij(ip).LE.klon_mpi_end) THEN 641 fieldok(ip,n)=buffer_omp(nptabij(ip)-klon_mpi_begin+1,n) 642 ENDIF 643 ENDDO 644 ENDDO 645 ENDIF 646 CALL histwrite(nid_files(iff),var%name,itau_iophy,fieldok,npstn*nlev,index3d) 647 ENDIF 648 deallocate(index3d) 649 deallocate(fieldok) 650 ENDIF 651 ENDDO 652 !$OMP END MASTER 653 END SUBROUTINE histwrite3d_phy 453 654 454 655 end module iophy -
LMDZ5/trunk/libf/phylmd/phys_output_mod.F90
r1785 r1791 12 12 MODULE phys_output_mod 13 13 USE indice_sol_mod 14 USE phys_output_var_mod 15 USE phys_output_ctrlout_mod 16 USE aero_mod, only : naero_spc,name_aero 14 17 15 18 IMPLICIT NONE 16 19 17 private histdef2d, histdef3d, conf_physoutputs 18 19 20 integer, parameter :: nfiles = 6 21 logical, dimension(nfiles), save :: clef_files 22 logical, dimension(nfiles), save :: clef_stations 23 integer, dimension(nfiles), save :: lev_files 24 integer, dimension(nfiles), save :: nid_files 25 integer, dimension(nfiles), save :: nnid_files 26 !!$OMP THREADPRIVATE(clef_files, clef_stations, lev_files,nid_files,nnid_files) 27 integer, dimension(nfiles), private, save :: nnhorim 28 29 integer, dimension(nfiles), private, save :: nhorim, nvertm 30 integer, dimension(nfiles), private, save :: nvertap, nvertbp, nvertAlt 31 ! integer, dimension(nfiles), private, save :: nvertp0 32 real, dimension(nfiles), private, save :: zoutm 33 real, private, save :: zdtime 34 CHARACTER(len=20), dimension(nfiles), private, save :: type_ecri 35 !$OMP THREADPRIVATE(nhorim, nvertm, zoutm,zdtime,type_ecri) 36 ! swaero_diag : flag indicates if it is necessary to do calculation for some aerosol diagnostics 37 logical, save :: swaero_diag=.FALSE. 38 39 40 ! integer, save :: nid_hf3d 41 42 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 43 !! Definition pour chaque variable du niveau d ecriture dans chaque fichier 44 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!/ histmth, histday, histhf, histins /),'!!!!!!!!!!!! 45 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 46 47 integer, private:: levmin(nfiles) = 1 48 integer, private:: levmax(nfiles) 49 50 TYPE ctrl_out 51 integer,dimension(6) :: flag 52 character(len=20) :: name 53 END TYPE ctrl_out 54 55 !!! Comosentes de la coordonnee sigma-hybride 56 !!! Ap et Bp 57 type(ctrl_out),save :: o_Ahyb = ctrl_out((/ 1, 1, 1, 1, 1, 1 /), 'Ap') 58 type(ctrl_out),save :: o_Bhyb = ctrl_out((/ 1, 1, 1, 1, 1, 1 /), 'Bp') 59 type(ctrl_out),save :: o_Alt = ctrl_out((/ 1, 1, 1, 1, 1, 1 /), 'Alt') 60 61 !!! 1D 62 type(ctrl_out),save :: o_phis = ctrl_out((/ 1, 1, 10, 5, 1, 1 /), 'phis') 63 type(ctrl_out),save :: o_aire = ctrl_out((/ 1, 1, 10, 10, 1, 1 /),'aire') 64 type(ctrl_out),save :: o_contfracATM = ctrl_out((/ 10, 1, 1, 10, 10, 10 /),'contfracATM') 65 type(ctrl_out),save :: o_contfracOR = ctrl_out((/ 10, 1, 1, 10, 10, 10 /),'contfracOR') 66 type(ctrl_out),save :: o_aireTER = ctrl_out((/ 10, 10, 1, 10, 10, 10 /),'aireTER') 67 68 !!! 2D 69 type(ctrl_out),save :: o_flat = ctrl_out((/ 5, 1, 10, 10, 5, 10 /),'flat') 70 type(ctrl_out),save :: o_slp = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'slp') 71 type(ctrl_out),save :: o_tsol = ctrl_out((/ 1, 1, 1, 5, 10, 10 /),'tsol') 72 type(ctrl_out),save :: o_t2m = ctrl_out((/ 1, 1, 1, 5, 10, 10 /),'t2m') 73 type(ctrl_out),save :: o_t2m_min = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'t2m_min') 74 type(ctrl_out),save :: o_t2m_max = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'t2m_max') 75 type(ctrl_out),save,dimension(4) :: o_t2m_srf = (/ ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'t2m_ter'), & 76 ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'t2m_lic'), & 77 ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'t2m_oce'), & 78 ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'t2m_sic') /) 79 80 type(ctrl_out),save :: o_wind10m = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'wind10m') 81 type(ctrl_out),save :: o_wind10max = ctrl_out((/ 10, 1, 10, 10, 10, 10 /),'wind10max') 82 type(ctrl_out),save :: o_sicf = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'sicf') 83 type(ctrl_out),save :: o_q2m = ctrl_out((/ 1, 1, 1, 5, 10, 10 /),'q2m') 84 type(ctrl_out),save :: o_ustar = ctrl_out((/ 1, 1, 1, 5, 10, 10 /),'ustar') 85 type(ctrl_out),save :: o_u10m = ctrl_out((/ 1, 1, 1, 5, 10, 10 /),'u10m') 86 type(ctrl_out),save :: o_v10m = ctrl_out((/ 1, 1, 1, 5, 10, 10 /),'v10m') 87 type(ctrl_out),save :: o_psol = ctrl_out((/ 1, 1, 1, 5, 10, 10 /),'psol') 88 type(ctrl_out),save :: o_qsurf = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'qsurf') 89 90 type(ctrl_out),save,dimension(4) :: o_ustar_srf = (/ ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'ustar_ter'), & 91 ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'ustar_lic'), & 92 ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'ustar_oce'), & 93 ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'ustar_sic') /) 94 type(ctrl_out),save,dimension(4) :: o_u10m_srf = (/ ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'u10m_ter'), & 95 ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'u10m_lic'), & 96 ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'u10m_oce'), & 97 ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'u10m_sic') /) 98 99 type(ctrl_out),save,dimension(4) :: o_v10m_srf = (/ ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'v10m_ter'), & 100 ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'v10m_lic'), & 101 ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'v10m_oce'), & 102 ctrl_out((/ 10, 6, 10, 10, 10, 10 /),'v10m_sic') /) 103 104 type(ctrl_out),save :: o_qsol = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'qsol') 105 106 type(ctrl_out),save :: o_ndayrain = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'ndayrain') 107 type(ctrl_out),save :: o_precip = ctrl_out((/ 1, 1, 1, 10, 5, 10 /),'precip') 108 type(ctrl_out),save :: o_plul = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'plul') 109 110 type(ctrl_out),save :: o_pluc = ctrl_out((/ 1, 1, 1, 10, 5, 10 /),'pluc') 111 type(ctrl_out),save :: o_snow = ctrl_out((/ 1, 1, 10, 10, 5, 10 /),'snow') 112 type(ctrl_out),save :: o_evap = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'evap') 113 type(ctrl_out),save,dimension(4) :: o_evap_srf = (/ ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'evap_ter'), & 114 ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'evap_lic'), & 115 ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'evap_oce'), & 116 ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'evap_sic') /) 117 type(ctrl_out),save :: o_msnow = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'msnow') 118 type(ctrl_out),save :: o_fsnow = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'fsnow') 119 120 type(ctrl_out),save :: o_tops = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'tops') 121 type(ctrl_out),save :: o_tops0 = ctrl_out((/ 1, 5, 10, 10, 10, 10 /),'tops0') 122 type(ctrl_out),save :: o_topl = ctrl_out((/ 1, 1, 10, 5, 10, 10 /),'topl') 123 type(ctrl_out),save :: o_topl0 = ctrl_out((/ 1, 5, 10, 10, 10, 10 /),'topl0') 124 type(ctrl_out),save :: o_SWupTOA = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'SWupTOA') 125 type(ctrl_out),save :: o_SWupTOAclr = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'SWupTOAclr') 126 type(ctrl_out),save :: o_SWdnTOA = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'SWdnTOA') 127 type(ctrl_out),save :: o_SWdnTOAclr = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'SWdnTOAclr') 128 type(ctrl_out),save :: o_nettop = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'nettop') 129 130 type(ctrl_out),save :: o_SWup200 = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'SWup200') 131 type(ctrl_out),save :: o_SWup200clr = ctrl_out((/ 10, 1, 10, 10, 10, 10 /),'SWup200clr') 132 type(ctrl_out),save :: o_SWdn200 = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'SWdn200') 133 type(ctrl_out),save :: o_SWdn200clr = ctrl_out((/ 10, 1, 10, 10, 10, 10 /),'SWdn200clr') 134 135 ! arajouter 136 ! type(ctrl_out),save :: o_LWupTOA = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'LWupTOA') 137 ! type(ctrl_out),save :: o_LWupTOAclr = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'LWupTOAclr') 138 ! type(ctrl_out),save :: o_LWdnTOA = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'LWdnTOA') 139 ! type(ctrl_out),save :: o_LWdnTOAclr = ctrl_out((/ 1, 4, 10, 10, 10, 10 /),'LWdnTOAclr') 140 141 type(ctrl_out),save :: o_LWup200 = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'LWup200') 142 type(ctrl_out),save :: o_LWup200clr = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'LWup200clr') 143 type(ctrl_out),save :: o_LWdn200 = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'LWdn200') 144 type(ctrl_out),save :: o_LWdn200clr = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'LWdn200clr') 145 type(ctrl_out),save :: o_sols = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'sols') 146 type(ctrl_out),save :: o_sols0 = ctrl_out((/ 1, 5, 10, 10, 10, 10 /),'sols0') 147 type(ctrl_out),save :: o_soll = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'soll') 148 type(ctrl_out),save :: o_soll0 = ctrl_out((/ 1, 5, 10, 10, 10, 10 /),'soll0') 149 type(ctrl_out),save :: o_radsol = ctrl_out((/ 1, 7, 10, 10, 10, 10 /),'radsol') 150 type(ctrl_out),save :: o_SWupSFC = ctrl_out((/ 1, 4, 10, 10, 5, 10 /),'SWupSFC') 151 type(ctrl_out),save :: o_SWupSFCclr = ctrl_out((/ 1, 4, 10, 10, 5, 10 /),'SWupSFCclr') 152 type(ctrl_out),save :: o_SWdnSFC = ctrl_out((/ 1, 1, 10, 10, 5, 10 /),'SWdnSFC') 153 type(ctrl_out),save :: o_SWdnSFCclr = ctrl_out((/ 1, 4, 10, 10, 5, 10 /),'SWdnSFCclr') 154 type(ctrl_out),save :: o_LWupSFC = ctrl_out((/ 1, 4, 10, 10, 5, 10 /),'LWupSFC') 155 type(ctrl_out),save :: o_LWupSFCclr = ctrl_out((/ 1, 4, 10, 10, 5, 10 /),'LWupSFCclr') 156 type(ctrl_out),save :: o_LWdnSFC = ctrl_out((/ 1, 4, 10, 10, 5, 10 /),'LWdnSFC') 157 type(ctrl_out),save :: o_LWdnSFCclr = ctrl_out((/ 1, 4, 10, 10, 5, 10 /),'LWdnSFCclr') 158 type(ctrl_out),save :: o_bils = ctrl_out((/ 1, 2, 10, 5, 10, 10 /),'bils') 159 type(ctrl_out),save :: o_bils_tke = ctrl_out((/ 1, 2, 10, 5, 10, 10 /),'bils_tke') 160 type(ctrl_out),save :: o_bils_diss = ctrl_out((/ 1, 2, 10, 5, 10, 10 /),'bils_diss') 161 type(ctrl_out),save :: o_bils_ec = ctrl_out((/ 1, 2, 10, 5, 10, 10 /),'bils_ec') 162 type(ctrl_out),save :: o_bils_kinetic = ctrl_out((/ 1, 2, 10, 5, 10, 10 /),'bils_kinetic') 163 type(ctrl_out),save :: o_bils_enthalp = ctrl_out((/ 1, 2, 10, 5, 10, 10 /),'bils_enthalp') 164 type(ctrl_out),save :: o_bils_latent = ctrl_out((/ 1, 2, 10, 5, 10, 10 /),'bils_latent') 165 type(ctrl_out),save :: o_sens = ctrl_out((/ 1, 1, 10, 10, 5, 10 /),'sens') 166 type(ctrl_out),save :: o_fder = ctrl_out((/ 1, 2, 10, 10, 10, 10 /),'fder') 167 type(ctrl_out),save :: o_ffonte = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'ffonte') 168 type(ctrl_out),save :: o_fqcalving = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'fqcalving') 169 type(ctrl_out),save :: o_fqfonte = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'fqfonte') 170 171 type(ctrl_out),save :: o_taux = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'taux') 172 type(ctrl_out),save :: o_tauy = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'tauy') 173 type(ctrl_out),save,dimension(4) :: o_taux_srf = (/ ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'taux_ter'), & 174 ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'taux_lic'), & 175 ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'taux_oce'), & 176 ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'taux_sic') /) 177 178 type(ctrl_out),save,dimension(4) :: o_tauy_srf = (/ ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tauy_ter'), & 179 ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tauy_lic'), & 180 ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tauy_oce'), & 181 ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tauy_sic') /) 182 183 184 type(ctrl_out),save,dimension(4) :: o_pourc_srf = (/ ctrl_out((/ 1, 7, 10, 10, 10, 10 /),'pourc_ter'), & 185 ctrl_out((/ 1, 7, 10, 10, 10, 10 /),'pourc_lic'), & 186 ctrl_out((/ 1, 7, 10, 10, 10, 10 /),'pourc_oce'), & 187 ctrl_out((/ 1, 7, 10, 10, 10, 10 /),'pourc_sic') /) 188 189 type(ctrl_out),save,dimension(4) :: o_fract_srf = (/ ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'fract_ter'), & 190 ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'fract_lic'), & 191 ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'fract_oce'), & 192 ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'fract_sic') /) 193 194 type(ctrl_out),save,dimension(4) :: o_tsol_srf = (/ ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tsol_ter'), & 195 ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tsol_lic'), & 196 ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tsol_oce'), & 197 ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'tsol_sic') /) 198 199 type(ctrl_out),save,dimension(4) :: o_evappot_srf = (/ ctrl_out((/ 1, 6, 10, 10, 10, 10 /),'evappot_ter'), & 200 ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'evappot_lic'), & 201 ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'evappot_oce'), & 202 ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'evappot_sic') /) 203 204 type(ctrl_out),save,dimension(4) :: o_sens_srf = (/ ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'sens_ter'), & 205 ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'sens_lic'), & 206 ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'sens_oce'), & 207 ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'sens_sic') /) 208 209 type(ctrl_out),save,dimension(4) :: o_lat_srf = (/ ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'lat_ter'), & 210 ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'lat_lic'), & 211 ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'lat_oce'), & 212 ctrl_out((/ 1, 6, 10, 7, 10, 10 /),'lat_sic') /) 213 214 type(ctrl_out),save,dimension(4) :: o_flw_srf = (/ ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'flw_ter'), & 215 ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'flw_lic'), & 216 ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'flw_oce'), & 217 ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'flw_sic') /) 218 219 type(ctrl_out),save,dimension(4) :: o_fsw_srf = (/ ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'fsw_ter'), & 220 ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'fsw_lic'), & 221 ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'fsw_oce'), & 222 ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'fsw_sic') /) 223 224 type(ctrl_out),save,dimension(4) :: o_wbils_srf = (/ ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbils_ter'), & 225 ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbils_lic'), & 226 ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbils_oce'), & 227 ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbils_sic') /) 228 229 type(ctrl_out),save,dimension(4) :: o_wbilo_srf = (/ ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbilo_ter'), & 230 ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbilo_lic'), & 231 ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbilo_oce'), & 232 ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbilo_sic') /) 233 234 235 type(ctrl_out),save :: o_cdrm = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'cdrm') 236 type(ctrl_out),save :: o_cdrh = ctrl_out((/ 1, 10, 10, 7, 10, 10 /),'cdrh') 237 type(ctrl_out),save :: o_cldl = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'cldl') 238 type(ctrl_out),save :: o_cldm = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'cldm') 239 type(ctrl_out),save :: o_cldh = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'cldh') 240 type(ctrl_out),save :: o_cldt = ctrl_out((/ 1, 1, 2, 10, 5, 10 /),'cldt') 241 type(ctrl_out),save :: o_cldq = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'cldq') 242 type(ctrl_out),save :: o_lwp = ctrl_out((/ 1, 5, 10, 10, 10, 10 /),'lwp') 243 type(ctrl_out),save :: o_iwp = ctrl_out((/ 1, 5, 10, 10, 10, 10 /),'iwp') 244 type(ctrl_out),save :: o_ue = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'ue') 245 type(ctrl_out),save :: o_ve = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'ve') 246 type(ctrl_out),save :: o_uq = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'uq') 247 type(ctrl_out),save :: o_vq = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'vq') 248 249 type(ctrl_out),save :: o_cape = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'cape') 250 type(ctrl_out),save :: o_pbase = ctrl_out((/ 1, 5, 10, 10, 10, 10 /),'pbase') 251 type(ctrl_out),save :: o_ptop = ctrl_out((/ 1, 5, 10, 10, 10, 10 /),'ptop') 252 type(ctrl_out),save :: o_fbase = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'fbase') 253 type(ctrl_out),save :: o_plcl = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'plcl') 254 type(ctrl_out),save :: o_plfc = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'plfc') 255 type(ctrl_out),save :: o_wbeff = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'wbeff') 256 type(ctrl_out),save :: o_prw = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'prw') 257 258 type(ctrl_out),save :: o_s_pblh = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_pblh') 259 type(ctrl_out),save :: o_s_pblt = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_pblt') 260 type(ctrl_out),save :: o_s_lcl = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_lcl') 261 type(ctrl_out),save :: o_s_therm = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_therm') 262 !IM : Les champs suivants (s_capCL, s_oliqCL, s_cteiCL, s_trmb1, s_trmb2, s_trmb3) ne sont pas definis dans HBTM.F 263 ! type(ctrl_out),save :: o_s_capCL = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_capCL') 264 ! type(ctrl_out),save :: o_s_oliqCL = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_oliqCL') 265 ! type(ctrl_out),save :: o_s_cteiCL = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_cteiCL') 266 ! type(ctrl_out),save :: o_s_trmb1 = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_trmb1') 267 ! type(ctrl_out),save :: o_s_trmb2 = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_trmb2') 268 ! type(ctrl_out),save :: o_s_trmb3 = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'s_trmb3') 269 270 type(ctrl_out),save :: o_slab_bils = ctrl_out((/ 1, 1, 10, 10, 10, 10 /),'slab_bils_oce') 271 272 type(ctrl_out),save :: o_ale_bl = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'ale_bl') 273 type(ctrl_out),save :: o_alp_bl = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'alp_bl') 274 type(ctrl_out),save :: o_ale_wk = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'ale_wk') 275 type(ctrl_out),save :: o_alp_wk = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'alp_wk') 276 277 type(ctrl_out),save :: o_ale = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'ale') 278 type(ctrl_out),save :: o_alp = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'alp') 279 type(ctrl_out),save :: o_cin = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'cin') 280 type(ctrl_out),save :: o_wape = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'wape') 281 282 !!! nrlmd le 10/04/2012 283 284 !-------Spectre de thermiques de type 2 au LCL 285 type(ctrl_out),save :: o_n2 = ctrl_out((/ 1, 1, 1, 6, 10, 10 /),'n2') 286 type(ctrl_out),save :: o_s2 = ctrl_out((/ 1, 1, 1, 6, 10, 10 /),'s2') 287 288 !-------Déclenchement stochastique 289 type(ctrl_out),save :: o_proba_notrig = ctrl_out((/ 1, 1, 1, 6, 10, 10 /),'proba_notrig') 290 type(ctrl_out),save :: o_random_notrig = ctrl_out((/ 1, 1, 1, 6, 10, 10 /),'random_notrig') 291 type(ctrl_out),save :: o_ale_bl_stat = ctrl_out((/ 1, 1, 1, 6, 10, 10 /),'ale_bl_stat') 292 type(ctrl_out),save :: o_ale_bl_trig = ctrl_out((/ 1, 1, 1, 6, 10, 10 /),'ale_bl_trig') 293 294 !-------Fermeture statistique 295 type(ctrl_out),save :: o_alp_bl_det = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'alp_bl_det') 296 type(ctrl_out),save :: o_alp_bl_fluct_m = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'alp_bl_fluct_m') 297 type(ctrl_out),save :: o_alp_bl_fluct_tke = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'alp_bl_fluct_tke') 298 type(ctrl_out),save :: o_alp_bl_conv = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'alp_bl_conv') 299 type(ctrl_out),save :: o_alp_bl_stat = ctrl_out((/ 1, 1, 1, 10, 10, 10 /),'alp_bl_stat') 300 301 !!! fin nrlmd le 10/04/2012 302 303 ! Champs interpolles sur des niveaux de pression ??? a faire correctement 304 305 type(ctrl_out),save,dimension(7) :: o_uSTDlevs = (/ ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u850'), & 306 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u700'), & 307 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u500'), & 308 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u200'), & 309 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u100'), & 310 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u50'), & 311 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'u10') /) 312 313 314 type(ctrl_out),save,dimension(7) :: o_vSTDlevs = (/ ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v850'), & 315 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v700'), & 316 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v500'), & 317 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v200'), & 318 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v100'), & 319 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v50'), & 320 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'v10') /) 321 322 type(ctrl_out),save,dimension(7) :: o_wSTDlevs = (/ ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w850'), & 323 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w700'), & 324 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w500'), & 325 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w200'), & 326 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w100'), & 327 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w50'), & 328 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'w10') /) 329 330 type(ctrl_out),save,dimension(7) :: o_tSTDlevs = (/ ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t850'), & 331 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t700'), & 332 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t500'), & 333 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t200'), & 334 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t100'), & 335 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t50'), & 336 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'t10') /) 337 338 type(ctrl_out),save,dimension(7) :: o_qSTDlevs = (/ ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q850'), & 339 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q700'), & 340 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q500'), & 341 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q200'), & 342 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q100'), & 343 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q50'), & 344 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'q10') /) 345 346 type(ctrl_out),save,dimension(7) :: o_zSTDlevs = (/ ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z850'), & 347 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z700'), & 348 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z500'), & 349 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z200'), & 350 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z100'), & 351 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z50'), & 352 ctrl_out((/ 1, 7, 7, 10, 10, 10 /),'z10') /) 353 354 355 type(ctrl_out),save :: o_t_oce_sic = ctrl_out((/ 1, 10, 10, 10, 10, 10 /),'t_oce_sic') 356 357 type(ctrl_out),save :: o_weakinv = ctrl_out((/ 10, 1, 10, 10, 10, 10 /),'weakinv') 358 type(ctrl_out),save :: o_dthmin = ctrl_out((/ 10, 1, 10, 10, 10, 10 /),'dthmin') 359 type(ctrl_out),save,dimension(4) :: o_u10_srf = (/ ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'u10_ter'), & 360 ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'u10_lic'), & 361 ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'u10_oce'), & 362 ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'u10_sic') /) 363 364 type(ctrl_out),save,dimension(4) :: o_v10_srf = (/ ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'v10_ter'), & 365 ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'v10_lic'), & 366 ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'v10_oce'), & 367 ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'v10_sic') /) 368 369 type(ctrl_out),save :: o_cldtau = ctrl_out((/ 10, 5, 10, 10, 10, 10 /),'cldtau') 370 type(ctrl_out),save :: o_cldemi = ctrl_out((/ 10, 5, 10, 10, 10, 10 /),'cldemi') 371 type(ctrl_out),save :: o_rh2m = ctrl_out((/ 5, 5, 10, 10, 10, 10 /),'rh2m') 372 type(ctrl_out),save :: o_rh2m_min = ctrl_out((/ 10, 5, 10, 10, 10, 10 /),'rh2m_min') 373 type(ctrl_out),save :: o_rh2m_max = ctrl_out((/ 10, 5, 10, 10, 10, 10 /),'rh2m_max') 374 type(ctrl_out),save :: o_qsat2m = ctrl_out((/ 10, 5, 10, 10, 10, 10 /),'qsat2m') 375 type(ctrl_out),save :: o_tpot = ctrl_out((/ 10, 5, 10, 10, 10, 10 /),'tpot') 376 type(ctrl_out),save :: o_tpote = ctrl_out((/ 10, 5, 10, 10, 10, 10 /),'tpote') 377 type(ctrl_out),save :: o_tke = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'tke ') 378 type(ctrl_out),save :: o_tke_max = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'tke_max') 379 380 type(ctrl_out),save,dimension(4) :: o_tke_srf = (/ ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_ter'), & 381 ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_lic'), & 382 ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_oce'), & 383 ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_sic') /) 384 385 type(ctrl_out),save,dimension(4) :: o_tke_max_srf = (/ ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_max_ter'), & 386 ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_max_lic'), & 387 ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_max_oce'), & 388 ctrl_out((/ 10, 4, 10, 10, 10, 10 /),'tke_max_sic') /) 389 390 type(ctrl_out),save :: o_kz = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'kz') 391 type(ctrl_out),save :: o_kz_max = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'kz_max') 392 type(ctrl_out),save :: o_SWnetOR = ctrl_out((/ 10, 10, 2, 10, 10, 10 /),'SWnetOR') 393 type(ctrl_out),save :: o_SWdownOR = ctrl_out((/ 10, 10, 2, 10, 10, 10 /),'SWdownOR') 394 type(ctrl_out),save :: o_LWdownOR = ctrl_out((/ 10, 10, 2, 10, 10, 10 /),'LWdownOR') 395 396 type(ctrl_out),save :: o_snowl = ctrl_out((/ 10, 1, 10, 10, 10, 10 /),'snowl') 397 type(ctrl_out),save :: o_cape_max = ctrl_out((/ 10, 1, 10, 10, 10, 10 /),'cape_max') 398 type(ctrl_out),save :: o_solldown = ctrl_out((/ 10, 1, 10, 10, 10, 10 /),'solldown') 399 400 type(ctrl_out),save :: o_dtsvdfo = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'dtsvdfo') 401 type(ctrl_out),save :: o_dtsvdft = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'dtsvdft') 402 type(ctrl_out),save :: o_dtsvdfg = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'dtsvdfg') 403 type(ctrl_out),save :: o_dtsvdfi = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'dtsvdfi') 404 type(ctrl_out),save :: o_rugs = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'rugs') 405 406 type(ctrl_out),save :: o_topswad = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'topswad') 407 type(ctrl_out),save :: o_topswad0 = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'topswad0') 408 type(ctrl_out),save :: o_topswai = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'topswai') 409 type(ctrl_out),save :: o_solswad = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'solswad') 410 type(ctrl_out),save :: o_solswad0 = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'solswad0') 411 type(ctrl_out),save :: o_solswai = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'solswai') 412 413 ! type(ctrl_out),save,dimension(10) :: o_tausumaero = (/ ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_ASBCM'), & 414 type(ctrl_out),save,dimension(11) :: o_tausumaero = & 415 (/ ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_ASBCM'), & 416 ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_ASPOMM'), & 417 ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_ASSO4M'), & 418 ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_CSSO4M'), & 419 ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_SSSSM'), & 420 ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_ASSSM'), & 421 ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_CSSSM'), & 422 ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_CIDUSTM'), & 423 ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_AIBCM'), & 424 ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'OD550_AIPOMM'), & 425 ctrl_out((/ 2, 2, 10, 10, 10, 10 /),'OD550_STRAT') /) 426 427 type(ctrl_out),save :: o_od550aer = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'od550aer') 428 type(ctrl_out),save :: o_od865aer = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'od865aer') 429 type(ctrl_out),save :: o_absvisaer = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'absvisaer') 430 type(ctrl_out),save :: o_od550lt1aer = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'od550lt1aer') 431 432 type(ctrl_out),save :: o_sconcso4 = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'sconcso4') 433 type(ctrl_out),save :: o_sconcoa = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'sconcoa') 434 type(ctrl_out),save :: o_sconcbc = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'sconcbc') 435 type(ctrl_out),save :: o_sconcss = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'sconcss') 436 type(ctrl_out),save :: o_sconcdust = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'sconcdust') 437 type(ctrl_out),save :: o_concso4 = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'concso4') 438 type(ctrl_out),save :: o_concoa = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'concoa') 439 type(ctrl_out),save :: o_concbc = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'concbc') 440 type(ctrl_out),save :: o_concss = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'concss') 441 type(ctrl_out),save :: o_concdust = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'concdust') 442 type(ctrl_out),save :: o_loadso4 = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'loadso4') 443 type(ctrl_out),save :: o_loadoa = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'loadoa') 444 type(ctrl_out),save :: o_loadbc = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'loadbc') 445 type(ctrl_out),save :: o_loadss = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'loadss') 446 type(ctrl_out),save :: o_loaddust = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'loaddust') 447 448 type(ctrl_out),save :: o_swtoaas_nat = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swtoaas_nat') 449 type(ctrl_out),save :: o_swsrfas_nat = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swsrfas_nat') 450 type(ctrl_out),save :: o_swtoacs_nat = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swtoacs_nat') 451 type(ctrl_out),save :: o_swsrfcs_nat = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swsrfcs_nat') 452 453 type(ctrl_out),save :: o_swtoaas_ant = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swtoaas_ant') 454 type(ctrl_out),save :: o_swsrfas_ant = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swsrfas_ant') 455 type(ctrl_out),save :: o_swtoacs_ant = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swtoacs_ant') 456 type(ctrl_out),save :: o_swsrfcs_ant = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swsrfcs_ant') 457 458 type(ctrl_out),save :: o_swtoacf_nat = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swtoacf_nat') 459 type(ctrl_out),save :: o_swsrfcf_nat = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swsrfcf_nat') 460 type(ctrl_out),save :: o_swtoacf_ant = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swtoacf_ant') 461 type(ctrl_out),save :: o_swsrfcf_ant = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swsrfcf_ant') 462 type(ctrl_out),save :: o_swtoacf_zero = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swtoacf_zero') 463 type(ctrl_out),save :: o_swsrfcf_zero = ctrl_out((/ 4, 6, 10, 10, 10, 10 /),'swsrfcf_zero') 464 465 type(ctrl_out),save :: o_cldncl = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'cldncl') 466 type(ctrl_out),save :: o_reffclwtop = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'reffclwtop') 467 type(ctrl_out),save :: o_cldnvi = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'cldnvi') 468 type(ctrl_out),save :: o_lcc = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'lcc') 469 470 471 !!!!!!!!!!!!!!!!!!!!!! 3D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 472 type(ctrl_out),save :: o_ec550aer = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'ec550aer') 473 type(ctrl_out),save :: o_lwcon = ctrl_out((/ 2, 5, 10, 10, 10, 10 /),'lwcon') 474 type(ctrl_out),save :: o_iwcon = ctrl_out((/ 2, 5, 10, 10, 10, 10 /),'iwcon') 475 type(ctrl_out),save :: o_temp = ctrl_out((/ 2, 3, 4, 10, 10, 10 /),'temp') 476 type(ctrl_out),save :: o_theta = ctrl_out((/ 2, 3, 4, 10, 10, 10 /),'theta') 477 type(ctrl_out),save :: o_ovap = ctrl_out((/ 2, 3, 4, 10, 10, 10 /),'ovap') 478 type(ctrl_out),save :: o_ovapinit = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'ovapinit') 479 type(ctrl_out),save :: o_oliq = ctrl_out((/ 2, 3, 4, 10, 10, 10 /),'oliq') 480 type(ctrl_out),save :: o_wvapp = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'wvapp') 481 type(ctrl_out),save :: o_geop = ctrl_out((/ 2, 3, 10, 10, 10, 10 /),'geop') 482 type(ctrl_out),save :: o_vitu = ctrl_out((/ 2, 3, 4, 6, 10, 10 /),'vitu') 483 type(ctrl_out),save :: o_vitv = ctrl_out((/ 2, 3, 4, 6, 10, 10 /),'vitv') 484 type(ctrl_out),save :: o_vitw = ctrl_out((/ 2, 3, 10, 6, 10, 10 /),'vitw') 485 type(ctrl_out),save :: o_pres = ctrl_out((/ 2, 3, 10, 10, 10, 10 /),'pres') 486 type(ctrl_out),save :: o_paprs = ctrl_out((/ 2, 3, 10, 10, 10, 10 /),'paprs') 487 type(ctrl_out),save :: o_mass = ctrl_out((/ 2, 3, 10, 10, 10, 10 /),'mass') 488 type(ctrl_out),save :: o_zfull = ctrl_out((/ 2, 3, 10, 10, 10, 10 /),'zfull') 489 type(ctrl_out),save :: o_zhalf = ctrl_out((/ 2, 3, 10, 10, 10, 10 /),'zhalf') 490 type(ctrl_out),save :: o_rneb = ctrl_out((/ 2, 5, 10, 10, 10, 10 /),'rneb') 491 type(ctrl_out),save :: o_rnebcon = ctrl_out((/ 2, 5, 10, 10, 10, 10 /),'rnebcon') 492 type(ctrl_out),save :: o_rnebls = ctrl_out((/ 2, 5, 10, 10, 10, 10 /),'rnebls') 493 type(ctrl_out),save :: o_rhum = ctrl_out((/ 2, 5, 10, 10, 10, 10 /),'rhum') 494 type(ctrl_out),save :: o_ozone = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'ozone') 495 type(ctrl_out),save :: o_ozone_light = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'ozone_daylight') 496 type(ctrl_out),save :: o_upwd = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'upwd') 497 type(ctrl_out),save :: o_dtphy = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'dtphy') 498 type(ctrl_out),save :: o_dqphy = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'dqphy') 499 type(ctrl_out),save :: o_pr_con_l = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'pr_con_l') 500 type(ctrl_out),save :: o_pr_con_i = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'pr_con_i') 501 type(ctrl_out),save :: o_pr_lsc_l = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'pr_lsc_l') 502 type(ctrl_out),save :: o_pr_lsc_i = ctrl_out((/ 2, 10, 10, 10, 10, 10 /),'pr_lsc_i') 503 type(ctrl_out),save :: o_re = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'re') 504 type(ctrl_out),save :: o_fl = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'fl') 505 type(ctrl_out),save :: o_scdnc = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'scdnc') 506 type(ctrl_out),save :: o_reffclws = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'reffclws') 507 type(ctrl_out),save :: o_reffclwc = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'reffclwc') 508 type(ctrl_out),save :: o_lcc3d = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'lcc3d') 509 type(ctrl_out),save :: o_lcc3dcon = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'lcc3dcon') 510 type(ctrl_out),save :: o_lcc3dstra = ctrl_out((/ 2, 6, 10, 10, 10, 10 /),'lcc3dstra') 511 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 512 513 type(ctrl_out),save,dimension(4) :: o_albe_srf = (/ ctrl_out((/ 3, 7, 10, 7, 10, 10 /),'albe_ter'), & 514 ctrl_out((/ 3, 7, 10, 7, 10, 10 /),'albe_lic'), & 515 ctrl_out((/ 3, 7, 10, 7, 10, 10 /),'albe_oce'), & 516 ctrl_out((/ 3, 7, 10, 7, 10, 10 /),'albe_sic') /) 517 518 type(ctrl_out),save,dimension(4) :: o_ages_srf = (/ ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'ages_ter'), & 519 ctrl_out((/ 3, 10, 10, 10, 10, 10 /),'ages_lic'), & 520 ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'ages_oce'), & 521 ctrl_out((/ 3, 10, 10, 10, 10, 10 /),'ages_sic') /) 522 523 type(ctrl_out),save,dimension(4) :: o_rugs_srf = (/ ctrl_out((/ 3, 6, 10, 10, 10, 10 /),'rugs_ter'), & 524 ctrl_out((/ 3, 6, 10, 10, 10, 10 /),'rugs_lic'), & 525 ctrl_out((/ 3, 6, 10, 10, 10, 10 /),'rugs_oce'), & 526 ctrl_out((/ 3, 6, 10, 10, 10, 10 /),'rugs_sic') /) 527 528 type(ctrl_out),save :: o_alb1 = ctrl_out((/ 3, 10, 10, 10, 10, 10 /),'alb1') 529 type(ctrl_out),save :: o_alb2 = ctrl_out((/ 3, 10, 10, 10, 10, 10 /),'alb2') 530 531 type(ctrl_out),save :: o_clwcon = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'clwcon') 532 type(ctrl_out),save :: o_Ma = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'Ma') 533 type(ctrl_out),save :: o_dnwd = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dnwd') 534 type(ctrl_out),save :: o_dnwd0 = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dnwd0') 535 type(ctrl_out),save :: o_mc = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'mc') 536 type(ctrl_out),save :: o_ftime_con = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'ftime_con') 537 type(ctrl_out),save :: o_dtdyn = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtdyn') 538 type(ctrl_out),save :: o_dqdyn = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dqdyn') 539 type(ctrl_out),save :: o_dudyn = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dudyn') !AXC 540 type(ctrl_out),save :: o_dvdyn = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dvdyn') !AXC 541 type(ctrl_out),save :: o_dtcon = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtcon') 542 type(ctrl_out),save :: o_ducon = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'ducon') 543 type(ctrl_out),save :: o_dvcon = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dvcon') 544 type(ctrl_out),save :: o_dqcon = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dqcon') 545 type(ctrl_out),save :: o_dtwak = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'dtwak') 546 type(ctrl_out),save :: o_dqwak = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'dqwak') 547 type(ctrl_out),save :: o_wake_h = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'wake_h') 548 type(ctrl_out),save :: o_wake_s = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'wake_s') 549 type(ctrl_out),save :: o_wake_deltat = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'wake_deltat') 550 type(ctrl_out),save :: o_wake_deltaq = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'wake_deltaq') 551 type(ctrl_out),save :: o_wake_omg = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'wake_omg') 552 type(ctrl_out),save :: o_wdtrainA = ctrl_out((/ 4, 1, 10, 4, 1, 10 /),'wdtrainA') !<<RomP 553 type(ctrl_out),save :: o_wdtrainM = ctrl_out((/ 4, 1, 10, 4, 1, 10 /),'wdtrainM') !<<RomP 554 type(ctrl_out),save :: o_Vprecip = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'Vprecip') 555 type(ctrl_out),save :: o_ftd = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'ftd') 556 type(ctrl_out),save :: o_fqd = ctrl_out((/ 4, 5, 10, 10, 10, 10 /),'fqd') 557 type(ctrl_out),save :: o_dtlsc = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtlsc') 558 type(ctrl_out),save :: o_dtlschr = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtlschr') 559 type(ctrl_out),save :: o_dqlsc = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dqlsc') 560 type(ctrl_out),save :: o_beta_prec = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'beta_prec') 561 type(ctrl_out),save :: o_dtvdf = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtvdf') 562 type(ctrl_out),save :: o_dtdis = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtdis') 563 type(ctrl_out),save :: o_dqvdf = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dqvdf') 564 type(ctrl_out),save :: o_dteva = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dteva') 565 type(ctrl_out),save :: o_dqeva = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dqeva') 566 567 !!!!!!!!!!!!!!!! Specifique thermiques 568 type(ctrl_out),save :: o_dqlscth = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'dqlscth') 569 type(ctrl_out),save :: o_dqlscst = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'dqlscst') 570 type(ctrl_out),save :: o_dtlscth = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'dtlscth') 571 type(ctrl_out),save :: o_dtlscst = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'dtlscst') 572 type(ctrl_out),save :: o_plulth = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'plulth') 573 type(ctrl_out),save :: o_plulst = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'plulst') 574 type(ctrl_out),save :: o_lmaxth = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'lmaxth') 575 type(ctrl_out),save :: o_ptconvth = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'ptconvth') 576 !!!!!!!!!!!!!!!!!!!!!!!! 577 578 579 type(ctrl_out),save :: o_ptconv = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'ptconv') 580 type(ctrl_out),save :: o_ratqs = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'ratqs') 581 type(ctrl_out),save :: o_dtthe = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtthe') 582 type(ctrl_out),save :: o_f_th = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'f_th') 583 type(ctrl_out),save :: o_e_th = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'e_th') 584 type(ctrl_out),save :: o_w_th = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'w_th') 585 type(ctrl_out),save :: o_lambda_th = ctrl_out((/ 10, 10, 10, 10, 10, 10 /),'lambda_th') 586 type(ctrl_out),save :: o_ftime_th = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'ftime_th') 587 type(ctrl_out),save :: o_q_th = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'q_th') 588 type(ctrl_out),save :: o_a_th = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'a_th') 589 type(ctrl_out),save :: o_d_th = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'d_th') 590 type(ctrl_out),save :: o_f0_th = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'f0_th') 591 type(ctrl_out),save :: o_zmax_th = ctrl_out((/ 4, 4, 4, 5, 10, 10 /),'zmax_th') 592 type(ctrl_out),save :: o_dqthe = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dqthe') 593 type(ctrl_out),save :: o_dtajs = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtajs') 594 type(ctrl_out),save :: o_dqajs = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dqajs') 595 type(ctrl_out),save :: o_dtswr = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtswr') 596 type(ctrl_out),save :: o_dtsw0 = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtsw0') 597 type(ctrl_out),save :: o_dtlwr = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtlwr') 598 type(ctrl_out),save :: o_dtlw0 = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtlw0') 599 type(ctrl_out),save :: o_dtec = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtec') 600 type(ctrl_out),save :: o_duvdf = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'duvdf') 601 type(ctrl_out),save :: o_dvvdf = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dvvdf') 602 type(ctrl_out),save :: o_duoro = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'duoro') 603 type(ctrl_out),save :: o_dvoro = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dvoro') 604 type(ctrl_out),save :: o_dulif = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dulif') 605 type(ctrl_out),save :: o_dvlif = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dvlif') 606 type(ctrl_out),save :: o_duhin = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'duhin') 607 type(ctrl_out),save :: o_dvhin = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dvhin') 608 type(ctrl_out),save :: o_dtoro = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtoro') 609 type(ctrl_out),save :: o_dtlif = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dtlif') 610 type(ctrl_out),save :: o_dthin = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dthin') 611 612 type(ctrl_out),save,allocatable :: o_trac(:) 613 type(ctrl_out),save,allocatable :: o_trac_cum(:) 614 615 type(ctrl_out),save :: o_rsu = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'rsu') 616 type(ctrl_out),save :: o_rsd = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'rsd') 617 type(ctrl_out),save :: o_rlu = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'rlu') 618 type(ctrl_out),save :: o_rld = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'rld') 619 type(ctrl_out),save :: o_rsucs = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'rsucs') 620 type(ctrl_out),save :: o_rsdcs = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'rsdcs') 621 type(ctrl_out),save :: o_rlucs = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'rlucs') 622 type(ctrl_out),save :: o_rldcs = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'rldcs') 623 624 type(ctrl_out),save :: o_tnt = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'tnt') 625 type(ctrl_out),save :: o_tntc = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'tntc') 626 type(ctrl_out),save :: o_tntr = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'tntr') 627 type(ctrl_out),save :: o_tntscpbl = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'tntscpbl') 628 629 type(ctrl_out),save :: o_tnhus = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'tnhus') 630 type(ctrl_out),save :: o_tnhusc = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'tnhusc') 631 type(ctrl_out),save :: o_tnhusscpbl = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'tnhusscpbl') 632 633 type(ctrl_out),save :: o_evu = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'evu') 634 635 type(ctrl_out),save :: o_h2o = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'h2o') 636 637 type(ctrl_out),save :: o_mcd = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'mcd') 638 type(ctrl_out),save :: o_dmc = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'dmc') 639 type(ctrl_out),save :: o_ref_liq = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'ref_liq') 640 type(ctrl_out),save :: o_ref_ice = ctrl_out((/ 4, 10, 10, 10, 10, 10 /),'ref_ice') 641 642 type(ctrl_out),save :: o_rsut4co2 = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rsut4co2') 643 type(ctrl_out),save :: o_rlut4co2 = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rlut4co2') 644 type(ctrl_out),save :: o_rsutcs4co2 = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rsutcs4co2') 645 type(ctrl_out),save :: o_rlutcs4co2 = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rlutcs4co2') 646 647 type(ctrl_out),save :: o_rsu4co2 = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rsu4co2') 648 type(ctrl_out),save :: o_rlu4co2 = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rlu4co2') 649 type(ctrl_out),save :: o_rsucs4co2 = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rsucs4co2') 650 type(ctrl_out),save :: o_rlucs4co2 = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rlucs4co2') 651 type(ctrl_out),save :: o_rsd4co2 = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rsd4co2') 652 type(ctrl_out),save :: o_rld4co2 = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rld4co2') 653 type(ctrl_out),save :: o_rsdcs4co2 = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rsdcs4co2') 654 type(ctrl_out),save :: o_rldcs4co2 = ctrl_out((/ 5, 10, 10, 10, 10, 10 /),'rldcs4co2') 20 PRIVATE histdef2d, histdef3d, conf_physoutputs 21 22 REAL, PRIVATE, SAVE :: zdtime 23 !$OMP THREADPRIVATE(zdtime) 24 655 25 656 26 … … 688 58 real,dimension(klon),intent(in) :: rlon 689 59 real,dimension(klon),intent(in) :: rlat 690 integer, intent(in) :: pim60 INTEGER, intent(in) :: pim 691 61 INTEGER, DIMENSION(pim) :: tabij 692 62 INTEGER,dimension(pim), intent(in) :: ipt, jpt … … 694 64 REAL,dimension(pim,2) :: plat_bounds, plon_bounds 695 65 696 integer:: jjmp1697 integer:: nbteta, nlevSTD, radpas698 logical:: ok_mensuel, ok_journe, ok_hf, ok_instan699 logical:: ok_LES,ok_ade,ok_aie,flag_aerosol_strat700 logical:: new_aod, aerosol_couple701 integer, intent(in):: read_climoz ! read ozone climatology66 INTEGER :: jjmp1 67 INTEGER :: nbteta, nlevSTD, radpas 68 LOGICAL :: ok_mensuel, ok_journe, ok_hf, ok_instan 69 LOGICAL :: ok_LES,ok_ade,ok_aie,flag_aerosol_strat 70 LOGICAL :: new_aod, aerosol_couple 71 INTEGER, intent(in):: read_climoz ! read ozone climatology 702 72 ! Allowed values are 0, 1 and 2 703 73 ! 0: do not read an ozone climatology … … 706 76 ! climatology and the daylight climatology 707 77 708 real :: dtime 709 integer :: idayref 710 real :: zjulian 711 real, dimension(klev) :: Ahyb, Bhyb, Alt 712 character(len=4), dimension(nlevSTD) :: clevSTD 713 integer :: nsrf, k, iq, iiq, iff, i, j, ilev 714 integer :: naero 715 logical :: ok_veget 716 integer :: iflag_pbl 717 CHARACTER(len=4) :: bb2 718 CHARACTER(len=2) :: bb3 719 character(len=6) :: type_ocean 720 CHARACTER(len=3) :: ctetaSTD(nbteta) 721 real, dimension(nfiles) :: ecrit_files 722 CHARACTER(len=20), dimension(nfiles) :: phys_out_filenames 723 INTEGER, dimension(iim*jjmp1) :: ndex2d 724 INTEGER, dimension(iim*jjmp1*klev) :: ndex3d 725 integer :: imin_ins, imax_ins 726 integer :: jmin_ins, jmax_ins 727 integer, dimension(nfiles) :: phys_out_levmin, phys_out_levmax 728 integer, dimension(nfiles) :: phys_out_filelevels 729 CHARACTER(len=20), dimension(nfiles) :: type_ecri_files, phys_out_filetypes 730 character(len=20), dimension(nfiles) :: chtimestep = (/ 'DefFreq', 'DefFreq','DefFreq', 'DefFreq', 'DefFreq', 'DefFreq' /) 731 logical, dimension(nfiles) :: phys_out_filekeys 732 logical, dimension(nfiles) :: phys_out_filestations 78 REAL :: dtime 79 INTEGER :: idayref 80 REAL :: zjulian 81 REAL, DIMENSION(klev) :: Ahyb, Bhyb, Alt 82 CHARACTER(LEN=4), DIMENSION(nlevSTD) :: clevSTD 83 INTEGER :: nsrf, k, iq, iiq, iff, i, j, ilev 84 INTEGER :: naero 85 LOGICAL :: ok_veget 86 INTEGER :: iflag_pbl 87 CHARACTER(LEN=4) :: bb2 88 CHARACTER(LEN=2) :: bb3 89 CHARACTER(LEN=6) :: type_ocean 90 CHARACTER(LEN=3) :: ctetaSTD(nbteta) 91 REAL, DIMENSION(nfiles) :: ecrit_files 92 CHARACTER(LEN=20), DIMENSION(nfiles) :: phys_out_filenames 93 INTEGER, DIMENSION(iim*jjmp1) :: ndex2d 94 INTEGER, DIMENSION(iim*jjmp1*klev) :: ndex3d 95 INTEGER :: imin_ins, imax_ins 96 INTEGER :: jmin_ins, jmax_ins 97 INTEGER, DIMENSION(nfiles) :: phys_out_levmin, phys_out_levmax 98 INTEGER, DIMENSION(nfiles) :: phys_out_filelevels 99 CHARACTER(LEN=20), DIMENSION(nfiles) :: chtimestep = (/ 'DefFreq', 'DefFreq','DefFreq', 'DefFreq', 'DefFreq', 'DefFreq' /) 100 LOGICAL, DIMENSION(nfiles) :: phys_out_filekeys 101 LOGICAL, DIMENSION(nfiles) :: phys_out_filestations 733 102 734 103 !!!!!!!!!! stockage dans une region limitee pour chaque fichier !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 735 104 ! entre [phys_out_lonmin,phys_out_lonmax] et [phys_out_latmin,phys_out_latmax] 736 105 737 logical, dimension(nfiles), save :: phys_out_regfkey = (/ .false., .false., .false., .false., .false., .false. /)738 real, dimension(nfiles), save:: phys_out_lonmin = (/ -180., -180., -180., -180., -180., -180. /)739 real, dimension(nfiles), save:: phys_out_lonmax = (/ 180., 180., 180., 180., 180., 180. /)740 real, dimension(nfiles), save:: phys_out_latmin = (/ -90., -90., -90., -90., -90., -90. /)741 real, dimension(nfiles), save:: phys_out_latmax = (/ 90., 90., 90., 90., 90., 90. /)742 743 write(lunout,*) 'Debut phys_output_mod.F90'106 LOGICAL, DIMENSION(nfiles), SAVE :: phys_out_regfkey = (/ .FALSE., .FALSE., .FALSE., .FALSE., .FALSE., .FALSE. /) 107 REAL, DIMENSION(nfiles), SAVE :: phys_out_lonmin = (/ -180., -180., -180., -180., -180., -180. /) 108 REAL, DIMENSION(nfiles), SAVE :: phys_out_lonmax = (/ 180., 180., 180., 180., 180., 180. /) 109 REAL, DIMENSION(nfiles), SAVE :: phys_out_latmin = (/ -90., -90., -90., -90., -90., -90. /) 110 REAL, DIMENSION(nfiles), SAVE :: phys_out_latmax = (/ 90., 90., 90., 90., 90., 90. /) 111 112 WRITE(lunout,*) 'Debut phys_output_mod.F90' 744 113 ! Initialisations (Valeurs par defaut 745 114 746 if (.not. allocated(o_trac)) ALLOCATE(o_trac(nqtot))747 if (.not. allocated(o_trac_cum)) ALLOCATE(o_trac_cum(nqtot))115 IF (.NOT. ALLOCATED(o_trac)) ALLOCATE(o_trac(nqtot)) 116 IF (.NOT. ALLOCATED(o_trac_cum)) ALLOCATE(o_trac_cum(nqtot)) 748 117 749 118 levmax = (/ klev, klev, klev, klev, klev, klev /) … … 794 163 !! Lectures des parametres de sorties dans physiq.def 795 164 796 callgetin('phys_out_regfkey',phys_out_regfkey)797 callgetin('phys_out_lonmin',phys_out_lonmin)798 callgetin('phys_out_lonmax',phys_out_lonmax)799 callgetin('phys_out_latmin',phys_out_latmin)800 callgetin('phys_out_latmax',phys_out_latmax)165 CALL getin('phys_out_regfkey',phys_out_regfkey) 166 CALL getin('phys_out_lonmin',phys_out_lonmin) 167 CALL getin('phys_out_lonmax',phys_out_lonmax) 168 CALL getin('phys_out_latmin',phys_out_latmin) 169 CALL getin('phys_out_latmax',phys_out_latmax) 801 170 phys_out_levmin(:)=levmin(:) 802 callgetin('phys_out_levmin',levmin)171 CALL getin('phys_out_levmin',levmin) 803 172 phys_out_levmax(:)=levmax(:) 804 callgetin('phys_out_levmax',levmax)805 callgetin('phys_out_filenames',phys_out_filenames)173 CALL getin('phys_out_levmax',levmax) 174 CALL getin('phys_out_filenames',phys_out_filenames) 806 175 phys_out_filekeys(:)=clef_files(:) 807 callgetin('phys_out_filekeys',clef_files)176 CALL getin('phys_out_filekeys',clef_files) 808 177 phys_out_filestations(:)=clef_stations(:) 809 callgetin('phys_out_filestations',clef_stations)178 CALL getin('phys_out_filestations',clef_stations) 810 179 phys_out_filelevels(:)=lev_files(:) 811 callgetin('phys_out_filelevels',lev_files)812 callgetin('phys_out_filetimesteps',chtimestep)180 CALL getin('phys_out_filelevels',lev_files) 181 CALL getin('phys_out_filetimesteps',chtimestep) 813 182 phys_out_filetypes(:)=type_ecri(:) 814 callgetin('phys_out_filetypes',type_ecri)183 CALL getin('phys_out_filetypes',type_ecri) 815 184 816 185 type_ecri_files(:)=type_ecri(:) 817 186 818 write(lunout,*)'phys_out_lonmin=',phys_out_lonmin819 write(lunout,*)'phys_out_lonmax=',phys_out_lonmax820 write(lunout,*)'phys_out_latmin=',phys_out_latmin821 write(lunout,*)'phys_out_latmax=',phys_out_latmax822 write(lunout,*)'phys_out_filenames=',phys_out_filenames823 write(lunout,*)'phys_out_filetypes=',type_ecri824 write(lunout,*)'phys_out_filekeys=',clef_files825 write(lunout,*)'phys_out_filestations=',clef_stations826 write(lunout,*)'phys_out_filelevels=',lev_files187 WRITE(lunout,*)'phys_out_lonmin=',phys_out_lonmin 188 WRITE(lunout,*)'phys_out_lonmax=',phys_out_lonmax 189 WRITE(lunout,*)'phys_out_latmin=',phys_out_latmin 190 WRITE(lunout,*)'phys_out_latmax=',phys_out_latmax 191 WRITE(lunout,*)'phys_out_filenames=',phys_out_filenames 192 WRITE(lunout,*)'phys_out_filetypes=',type_ecri 193 WRITE(lunout,*)'phys_out_filekeys=',clef_files 194 WRITE(lunout,*)'phys_out_filestations=',clef_stations 195 WRITE(lunout,*)'phys_out_filelevels=',lev_files 827 196 828 197 !!!!!!!!!!!!!!!!!!!!!!! Boucle sur les fichiers !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! … … 834 203 835 204 ! Calcul des Ahyb, Bhyb et Alt 836 dok=1,klev205 DO k=1,klev 837 206 Ahyb(k)=(ap(k)+ap(k+1))/2. 838 207 Bhyb(k)=(bp(k)+bp(k+1))/2. 839 208 Alt(k)=log(preff/presnivs(k))*8. 840 enddo209 ENDDO 841 210 ! if(prt_level.ge.1) then 842 write(lunout,*)'Ap Hybrid = ',Ahyb(1:klev)843 write(lunout,*)'Bp Hybrid = ',Bhyb(1:klev)844 write(lunout,*)'Alt approx des couches pour une haut d echelle de 8km = ',Alt(1:klev)211 WRITE(lunout,*)'Ap Hybrid = ',Ahyb(1:klev) 212 WRITE(lunout,*)'Bp Hybrid = ',Bhyb(1:klev) 213 WRITE(lunout,*)'Alt approx des couches pour une haut d echelle de 8km = ',Alt(1:klev) 845 214 ! endif 846 215 DO iff=1,nfiles 847 216 848 217 ! Calculate ecrit_files for all files 849 if( chtimestep(iff).eq.'DefFreq' ) then218 IF ( chtimestep(iff).eq.'DefFreq' ) then 850 219 ! Par defaut ecrit_files = (ecrit_mensuel ecrit_jour ecrit_hf ...)*86400. 851 220 ecrit_files(iff)=ecrit_files(iff)*86400. 852 else853 callconvers_timesteps(chtimestep(iff),dtime,ecrit_files(iff))854 endif855 write(lunout,*)'ecrit_files(',iff,')= ',ecrit_files(iff)221 ELSE 222 CALL convers_timesteps(chtimestep(iff),dtime,ecrit_files(iff)) 223 ENDIF 224 WRITE(lunout,*)'ecrit_files(',iff,')= ',ecrit_files(iff) 856 225 857 226 zoutm(iff) = ecrit_files(iff) ! Frequence ou l on ecrit en seconde … … 873 242 !!!!!!!!!!!!!!!!! Traitement dans le cas ou l'on veut stocker sur un domaine limite !! 874 243 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 875 if(phys_out_regfkey(iff)) then244 IF (phys_out_regfkey(iff)) then 876 245 877 246 imin_ins=1 … … 882 251 ! correction abderr 883 252 do i=1,iim 884 write(lunout,*)'io_lon(i)=',io_lon(i)885 if(io_lon(i).le.phys_out_lonmin(iff)) imin_ins=i886 if(io_lon(i).le.phys_out_lonmax(iff)) imax_ins=i+1253 WRITE(lunout,*)'io_lon(i)=',io_lon(i) 254 IF (io_lon(i).le.phys_out_lonmin(iff)) imin_ins=i 255 IF (io_lon(i).le.phys_out_lonmax(iff)) imax_ins=i+1 887 256 enddo 888 257 889 258 do j=1,jjmp1 890 write(lunout,*)'io_lat(j)=',io_lat(j)891 if(io_lat(j).ge.phys_out_latmin(iff)) jmax_ins=j+1892 if(io_lat(j).ge.phys_out_latmax(iff)) jmin_ins=j259 WRITE(lunout,*)'io_lat(j)=',io_lat(j) 260 IF (io_lat(j).ge.phys_out_latmin(iff)) jmax_ins=j+1 261 IF (io_lat(j).ge.phys_out_latmax(iff)) jmin_ins=j 893 262 enddo 894 263 895 write(lunout,*)'On stoke le fichier histoire numero ',iff,' sur ', &264 WRITE(lunout,*)'On stoke le fichier histoire numero ',iff,' sur ', & 896 265 imin_ins,imax_ins,jmin_ins,jmax_ins 897 write(lunout,*)'longitudes : ', &266 WRITE(lunout,*)'longitudes : ', & 898 267 io_lon(imin_ins),io_lon(imax_ins), & 899 268 'latitudes : ', & … … 906 275 !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 907 276 !IM fichiers stations 908 else if(clef_stations(iff)) THEN909 910 write(lunout,*)'phys_output_mod phys_out_filenames=',phys_out_filenames(iff)911 912 callhistbeg_phy_all(rlon,rlat,pim,tabij,ipt,jpt,plon,plat,plon_bounds,plat_bounds, &277 else IF (clef_stations(iff)) THEN 278 279 WRITE(lunout,*)'phys_output_mod phys_out_filenames=',phys_out_filenames(iff) 280 281 CALL histbeg_phy_all(rlon,rlat,pim,tabij,ipt,jpt,plon,plat,plon_bounds,plat_bounds, & 913 282 phys_out_filenames(iff), & 914 283 itau_phy,zjulian,dtime,nhorim(iff),nid_files(iff)) … … 946 315 ! 1,preff,nvertp0(iff)) 947 316 !!! Champs 1D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 948 IF (.NOT.clef_stations(iff)) THEN 949 ! 950 !IM: there is no way to have one single value in a netcdf file 951 ! 952 type_ecri(1) = 'once' 953 type_ecri(2) = 'once' 954 type_ecri(3) = 'once' 955 type_ecri(4) = 'once' 956 type_ecri(5) = 'once' 957 type_ecri(6) = 'once' 958 CALL histdef2d(iff,clef_stations(iff),o_aire%flag,o_aire%name,"Grid area", "-") 959 CALL histdef2d(iff,clef_stations(iff),o_contfracATM%flag,o_contfracATM%name,"% sfce ter+lic", "-") 960 ENDIF 961 type_ecri(:) = type_ecri_files(:) 317 CALL histdef2d(iff,o_aire) 318 CALL histdef2d(iff,o_contfracATM) 962 319 963 320 !!! Champs 2D !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!! 964 CALL histdef2d(iff,clef_stations(iff),o_phis%flag,o_phis%name,"Surface geop.height", "m2/s2" ) 965 CALL histdef2d(iff,clef_stations(iff),o_contfracOR%flag,o_contfracOR%name,"% sfce terre OR", "-" ) 966 CALL histdef2d(iff,clef_stations(iff),o_aireTER%flag,o_aireTER%name,"Grid area CONT", "-" ) 967 CALL histdef2d(iff,clef_stations(iff),o_flat%flag,o_flat%name, "Latent heat flux", "W/m2") 968 CALL histdef2d(iff,clef_stations(iff),o_slp%flag,o_slp%name, "Sea Level Pressure", "Pa" ) 969 CALL histdef2d(iff,clef_stations(iff),o_tsol%flag,o_tsol%name, "Surface Temperature", "K") 970 CALL histdef2d(iff,clef_stations(iff),o_t2m%flag,o_t2m%name, "Temperature 2m", "K" ) 971 IF (.NOT.clef_stations(iff)) THEN 972 ! 973 !IM: there is no way to have one single value in a netcdf file 974 ! 975 type_ecri(1) = 't_min(X)' 976 type_ecri(2) = 't_min(X)' 977 type_ecri(3) = 't_min(X)' 978 type_ecri(4) = 't_min(X)' 979 type_ecri(5) = 't_min(X)' 980 type_ecri(6) = 't_min(X)' 981 CALL histdef2d(iff,clef_stations(iff),o_t2m_min%flag,o_t2m_min%name, "Temp 2m min", "K" ) 982 type_ecri(1) = 't_max(X)' 983 type_ecri(2) = 't_max(X)' 984 type_ecri(3) = 't_max(X)' 985 type_ecri(4) = 't_max(X)' 986 type_ecri(5) = 't_max(X)' 987 type_ecri(6) = 't_max(X)' 988 CALL histdef2d(iff,clef_stations(iff),o_t2m_max%flag,o_t2m_max%name, "Temp 2m max", "K" ) 989 ENDIF 990 type_ecri(:) = type_ecri_files(:) 991 CALL histdef2d(iff,clef_stations(iff),o_wind10m%flag,o_wind10m%name, "10-m wind speed", "m/s") 992 CALL histdef2d(iff,clef_stations(iff),o_wind10max%flag,o_wind10max%name, "10m wind speed max", "m/s") 993 CALL histdef2d(iff,clef_stations(iff),o_sicf%flag,o_sicf%name, "Sea-ice fraction", "-" ) 994 CALL histdef2d(iff,clef_stations(iff),o_q2m%flag,o_q2m%name, "Specific humidity 2m", "kg/kg") 995 CALL histdef2d(iff,clef_stations(iff),o_ustar%flag,o_ustar%name, "Friction velocity", "m/s" ) 996 CALL histdef2d(iff,clef_stations(iff),o_u10m%flag,o_u10m%name, "Vent zonal 10m", "m/s" ) 997 CALL histdef2d(iff,clef_stations(iff),o_v10m%flag,o_v10m%name, "Vent meridien 10m", "m/s") 998 CALL histdef2d(iff,clef_stations(iff),o_psol%flag,o_psol%name, "Surface Pressure", "Pa" ) 999 CALL histdef2d(iff,clef_stations(iff),o_qsurf%flag,o_qsurf%name, "Surface Air humidity", "kg/kg") 1000 1001 if (.not. ok_veget) then 1002 CALL histdef2d(iff,clef_stations(iff),o_qsol%flag,o_qsol%name, "Soil watter content", "mm" ) 1003 endif 1004 1005 type_ecri(1) = 'inst(X)' 1006 type_ecri(2) = 'inst(X)' 1007 type_ecri(3) = 'inst(X)' 1008 type_ecri(4) = 'inst(X)' 1009 type_ecri(5) = 'inst(X)' 1010 type_ecri(6) = 'inst(X)' 1011 CALL histdef2d(iff,clef_stations(iff),o_ndayrain%flag,o_ndayrain%name, "Number of dayrain(liq+sol)", "-") 1012 type_ecri(:) = type_ecri_files(:) 1013 CALL histdef2d(iff,clef_stations(iff),o_precip%flag,o_precip%name, "Precip Totale liq+sol", "kg/(s*m2)" ) 1014 CALL histdef2d(iff,clef_stations(iff),o_plul%flag,o_plul%name, "Large-scale Precip.", "kg/(s*m2)") 1015 CALL histdef2d(iff,clef_stations(iff),o_pluc%flag,o_pluc%name, "Convective Precip.", "kg/(s*m2)") 1016 CALL histdef2d(iff,clef_stations(iff),o_snow%flag,o_snow%name, "Snow fall", "kg/(s*m2)" ) 1017 CALL histdef2d(iff,clef_stations(iff),o_msnow%flag,o_msnow%name, "Surface snow amount", "kg/m2" ) 1018 CALL histdef2d(iff,clef_stations(iff),o_fsnow%flag,o_fsnow%name, "Surface snow area fraction", "-" ) 1019 CALL histdef2d(iff,clef_stations(iff),o_evap%flag,o_evap%name, "Evaporat", "kg/(s*m2)" ) 1020 CALL histdef2d(iff,clef_stations(iff),o_tops%flag,o_tops%name, "Solar rad. at TOA", "W/m2") 1021 CALL histdef2d(iff,clef_stations(iff),o_tops0%flag,o_tops0%name, "CS Solar rad. at TOA", "W/m2") 1022 CALL histdef2d(iff,clef_stations(iff),o_topl%flag,o_topl%name, "IR rad. at TOA", "W/m2" ) 1023 CALL histdef2d(iff,clef_stations(iff),o_topl0%flag,o_topl0%name, "IR rad. at TOA", "W/m2") 1024 CALL histdef2d(iff,clef_stations(iff),o_SWupTOA%flag,o_SWupTOA%name, "SWup at TOA", "W/m2") 1025 CALL histdef2d(iff,clef_stations(iff),o_SWupTOAclr%flag,o_SWupTOAclr%name, "SWup clear sky at TOA", "W/m2") 1026 CALL histdef2d(iff,clef_stations(iff),o_SWdnTOA%flag,o_SWdnTOA%name, "SWdn at TOA", "W/m2" ) 1027 CALL histdef2d(iff,clef_stations(iff),o_SWdnTOAclr%flag,o_SWdnTOAclr%name, "SWdn clear sky at TOA", "W/m2") 1028 CALL histdef2d(iff,clef_stations(iff),o_nettop%flag,o_nettop%name, "Net dn radiatif flux at TOA", "W/m2") 1029 CALL histdef2d(iff,clef_stations(iff),o_SWup200%flag,o_SWup200%name, "SWup at 200mb", "W/m2" ) 1030 CALL histdef2d(iff,clef_stations(iff),o_SWup200clr%flag,o_SWup200clr%name, "SWup clear sky at 200mb", "W/m2") 1031 CALL histdef2d(iff,clef_stations(iff),o_SWdn200%flag,o_SWdn200%name, "SWdn at 200mb", "W/m2" ) 1032 CALL histdef2d(iff,clef_stations(iff),o_SWdn200clr%flag,o_SWdn200clr%name, "SWdn clear sky at 200mb", "W/m2") 1033 CALL histdef2d(iff,clef_stations(iff),o_LWup200%flag,o_LWup200%name, "LWup at 200mb", "W/m2") 1034 CALL histdef2d(iff,clef_stations(iff),o_LWup200clr%flag,o_LWup200clr%name, "LWup clear sky at 200mb", "W/m2") 1035 CALL histdef2d(iff,clef_stations(iff),o_LWdn200%flag,o_LWdn200%name, "LWdn at 200mb", "W/m2") 1036 CALL histdef2d(iff,clef_stations(iff),o_LWdn200clr%flag,o_LWdn200clr%name, "LWdn clear sky at 200mb", "W/m2") 1037 CALL histdef2d(iff,clef_stations(iff),o_sols%flag,o_sols%name, "Solar rad. at surf.", "W/m2") 1038 CALL histdef2d(iff,clef_stations(iff),o_sols0%flag,o_sols0%name, "Solar rad. at surf.", "W/m2") 1039 CALL histdef2d(iff,clef_stations(iff),o_soll%flag,o_soll%name, "IR rad. at surface", "W/m2") 1040 CALL histdef2d(iff,clef_stations(iff),o_radsol%flag,o_radsol%name, "Rayonnement au sol", "W/m2") 1041 CALL histdef2d(iff,clef_stations(iff),o_soll0%flag,o_soll0%name, "IR rad. at surface", "W/m2") 1042 CALL histdef2d(iff,clef_stations(iff),o_SWupSFC%flag,o_SWupSFC%name, "SWup at surface", "W/m2") 1043 CALL histdef2d(iff,clef_stations(iff),o_SWupSFCclr%flag,o_SWupSFCclr%name, "SWup clear sky at surface", "W/m2") 1044 CALL histdef2d(iff,clef_stations(iff),o_SWdnSFC%flag,o_SWdnSFC%name, "SWdn at surface", "W/m2") 1045 CALL histdef2d(iff,clef_stations(iff),o_SWdnSFCclr%flag,o_SWdnSFCclr%name, "SWdn clear sky at surface", "W/m2") 1046 CALL histdef2d(iff,clef_stations(iff),o_LWupSFC%flag,o_LWupSFC%name, "Upwd. IR rad. at surface", "W/m2") 1047 CALL histdef2d(iff,clef_stations(iff),o_LWdnSFC%flag,o_LWdnSFC%name, "Down. IR rad. at surface", "W/m2") 1048 CALL histdef2d(iff,clef_stations(iff),o_LWupSFCclr%flag,o_LWupSFCclr%name, "CS Upwd. IR rad. at surface", "W/m2") 1049 CALL histdef2d(iff,clef_stations(iff),o_LWdnSFCclr%flag,o_LWdnSFCclr%name, "Down. CS IR rad. at surface", "W/m2") 1050 CALL histdef2d(iff,clef_stations(iff),o_bils%flag,o_bils%name, "Surf. total heat flux", "W/m2") 1051 CALL histdef2d(iff,clef_stations(iff),o_bils_ec%flag,o_bils_ec%name, "Surf. total heat flux", "W/m2") 1052 CALL histdef2d(iff,clef_stations(iff),o_bils_tke%flag,o_bils_tke%name, "Surf. total heat flux", "W/m2") 1053 CALL histdef2d(iff,clef_stations(iff),o_bils_diss%flag,o_bils_diss%name, "Surf. total heat flux", "W/m2") 1054 CALL histdef2d(iff,clef_stations(iff),o_bils_kinetic%flag,o_bils_kinetic%name, "Surf. total heat flux", "W/m2") 1055 CALL histdef2d(iff,clef_stations(iff),o_bils_enthalp%flag,o_bils_enthalp%name, "Surf. total heat flux", "W/m2") 1056 CALL histdef2d(iff,clef_stations(iff),o_bils_latent%flag,o_bils_latent%name, "Surf. total heat flux", "W/m2") 1057 CALL histdef2d(iff,clef_stations(iff),o_sens%flag,o_sens%name, "Sensible heat flux", "W/m2") 1058 CALL histdef2d(iff,clef_stations(iff),o_fder%flag,o_fder%name, "Heat flux derivation", "W/m2") 1059 CALL histdef2d(iff,clef_stations(iff),o_ffonte%flag,o_ffonte%name, "Thermal flux for snow melting", "W/m2") 1060 CALL histdef2d(iff,clef_stations(iff),o_fqcalving%flag,o_fqcalving%name, "Ice Calving", "kg/m2/s") 1061 CALL histdef2d(iff,clef_stations(iff),o_fqfonte%flag,o_fqfonte%name, "Land ice melt", "kg/m2/s") 1062 1063 CALL histdef2d(iff,clef_stations(iff),o_taux%flag,o_taux%name, "Zonal wind stress","Pa") 1064 CALL histdef2d(iff,clef_stations(iff),o_tauy%flag,o_tauy%name, "Meridional wind stress","Pa") 1065 1066 DO nsrf = 1, nbsrf 1067 CALL histdef2d(iff,clef_stations(iff),o_pourc_srf(nsrf)%flag,o_pourc_srf(nsrf)%name,"% "//clnsurf(nsrf),"%") 1068 CALL histdef2d(iff,clef_stations(iff),o_fract_srf(nsrf)%flag,o_fract_srf(nsrf)%name,"Fraction "//clnsurf(nsrf),"1") 1069 CALL histdef2d(iff,clef_stations(iff), & 1070 o_taux_srf(nsrf)%flag,o_taux_srf(nsrf)%name,"Zonal wind stress"//clnsurf(nsrf),"Pa") 1071 CALL histdef2d(iff,clef_stations(iff), & 1072 o_tauy_srf(nsrf)%flag,o_tauy_srf(nsrf)%name,"Meridional wind stress "//clnsurf(nsrf),"Pa") 1073 CALL histdef2d(iff,clef_stations(iff), & 1074 o_tsol_srf(nsrf)%flag,o_tsol_srf(nsrf)%name,"Temperature "//clnsurf(nsrf),"K") 1075 CALL histdef2d(iff,clef_stations(iff), & 1076 o_evappot_srf(nsrf)%flag,o_evappot_srf(nsrf)%name,"Temperature"//clnsurf(nsrf),"K") 1077 CALL histdef2d(iff,clef_stations(iff), & 1078 o_ustar_srf(nsrf)%flag,o_ustar_srf(nsrf)%name,"Friction velocity "//clnsurf(nsrf),"m/s") 1079 CALL histdef2d(iff,clef_stations(iff), & 1080 o_u10m_srf(nsrf)%flag,o_u10m_srf(nsrf)%name,"Vent Zonal 10m "//clnsurf(nsrf),"m/s") 1081 CALL histdef2d(iff,clef_stations(iff), & 1082 o_evap_srf(nsrf)%flag,o_evap_srf(nsrf)%name,"evaporation at surface "//clnsurf(nsrf),"kg/(s*m2)") 1083 CALL histdef2d(iff,clef_stations(iff), & 1084 o_v10m_srf(nsrf)%flag,o_v10m_srf(nsrf)%name,"Vent meredien 10m "//clnsurf(nsrf),"m/s") 1085 CALL histdef2d(iff,clef_stations(iff), & 1086 o_t2m_srf(nsrf)%flag,o_t2m_srf(nsrf)%name,"Temp 2m "//clnsurf(nsrf),"K") 1087 CALL histdef2d(iff,clef_stations(iff), & 1088 o_sens_srf(nsrf)%flag,o_sens_srf(nsrf)%name,"Sensible heat flux "//clnsurf(nsrf),"W/m2") 1089 CALL histdef2d(iff,clef_stations(iff), & 1090 o_lat_srf(nsrf)%flag,o_lat_srf(nsrf)%name,"Latent heat flux "//clnsurf(nsrf),"W/m2") 1091 CALL histdef2d(iff,clef_stations(iff), & 1092 o_flw_srf(nsrf)%flag,o_flw_srf(nsrf)%name,"LW "//clnsurf(nsrf),"W/m2") 1093 CALL histdef2d(iff,clef_stations(iff), & 1094 o_fsw_srf(nsrf)%flag,o_fsw_srf(nsrf)%name,"SW "//clnsurf(nsrf),"W/m2") 1095 CALL histdef2d(iff,clef_stations(iff), & 1096 o_wbils_srf(nsrf)%flag,o_wbils_srf(nsrf)%name,"Bilan sol "//clnsurf(nsrf),"W/m2" ) 1097 CALL histdef2d(iff,clef_stations(iff), & 1098 o_wbilo_srf(nsrf)%flag,o_wbilo_srf(nsrf)%name,"Bilan eau "//clnsurf(nsrf),"kg/(m2*s)") 1099 1100 1101 if (iflag_pbl>1 .and. lev_files(iff).gt.10 ) then 1102 CALL histdef2d(iff,clef_stations(iff), & 1103 o_tke_srf(nsrf)%flag,o_tke_srf(nsrf)%name,"Max Turb. Kinetic Energy "//clnsurf(nsrf),"-") 1104 1105 IF (.NOT.clef_stations(iff)) THEN 1106 ! 1107 !IM: there is no way to have one single value in a netcdf file 1108 ! 1109 type_ecri(1) = 't_max(X)' 1110 type_ecri(2) = 't_max(X)' 1111 type_ecri(3) = 't_max(X)' 1112 type_ecri(4) = 't_max(X)' 1113 type_ecri(5) = 't_max(X)' 1114 type_ecri(6) = 't_max(X)' 1115 CALL histdef2d(iff,clef_stations(iff), & 1116 o_tke_max_srf(nsrf)%flag,o_tke_max_srf(nsrf)%name,"Max Turb. Kinetic Energy "//clnsurf(nsrf),"-") 1117 type_ecri(:) = type_ecri_files(:) 1118 ENDIF 1119 1120 endif 1121 1122 1123 CALL histdef2d(iff,clef_stations(iff), & 1124 o_albe_srf(nsrf)%flag,o_albe_srf(nsrf)%name,"Albedo VIS surf. "//clnsurf(nsrf),"-") 1125 CALL histdef2d(iff,clef_stations(iff), & 1126 o_rugs_srf(nsrf)%flag,o_rugs_srf(nsrf)%name,"Surface roughness "//clnsurf(nsrf),"m") 1127 CALL histdef2d(iff,clef_stations(iff), & 1128 o_ages_srf(nsrf)%flag,o_ages_srf(nsrf)%name,"Snow age", "day") 1129 END DO 1130 1131 IF (new_aod .AND. (.NOT. aerosol_couple)) THEN 1132 IF (ok_ade.OR.ok_aie) THEN 1133 1134 CALL histdef2d(iff,clef_stations(iff), & 1135 o_od550aer%flag,o_od550aer%name, "Total aerosol optical depth at 550nm", "-") 1136 CALL histdef2d(iff,clef_stations(iff), & 1137 o_od865aer%flag,o_od865aer%name, "Total aerosol optical depth at 870nm", "-") 1138 CALL histdef2d(iff,clef_stations(iff), & 1139 o_absvisaer%flag,o_absvisaer%name, "Absorption aerosol visible optical depth", "-") 1140 CALL histdef2d(iff,clef_stations(iff), & 1141 o_od550lt1aer%flag,o_od550lt1aer%name, "Fine mode optical depth", "-") 1142 1143 1144 CALL histdef2d(iff,clef_stations(iff), & 1145 o_sconcso4%flag,o_sconcso4%name,"Surface Concentration of Sulfate ","kg/m3") 1146 CALL histdef2d(iff,clef_stations(iff), & 1147 o_sconcoa%flag,o_sconcoa%name,"Surface Concentration of Organic Aerosol ","kg/m3") 1148 CALL histdef2d(iff,clef_stations(iff), & 1149 o_sconcbc%flag,o_sconcbc%name,"Surface Concentration of Black Carbon ","kg/m3") 1150 CALL histdef2d(iff,clef_stations(iff), & 1151 o_sconcss%flag,o_sconcss%name,"Surface Concentration of Sea Salt ","kg/m3") 1152 CALL histdef2d(iff,clef_stations(iff), & 1153 o_sconcdust%flag,o_sconcdust%name,"Surface Concentration of Dust ","kg/m3") 1154 CALL histdef3d(iff,clef_stations(iff), & 1155 o_concso4%flag,o_concso4%name,"Concentration of Sulfate ","kg/m3") 1156 CALL histdef3d(iff,clef_stations(iff), & 1157 o_concoa%flag,o_concoa%name,"Concentration of Organic Aerosol ","kg/m3") 1158 CALL histdef3d(iff,clef_stations(iff), & 1159 o_concbc%flag,o_concbc%name,"Concentration of Black Carbon ","kg/m3") 1160 CALL histdef3d(iff,clef_stations(iff), & 1161 o_concss%flag,o_concss%name,"Concentration of Sea Salt ","kg/m3") 1162 CALL histdef3d(iff,clef_stations(iff), & 1163 o_concdust%flag,o_concdust%name,"Concentration of Dust ","kg/m3") 1164 CALL histdef2d(iff,clef_stations(iff), & 1165 o_loadso4%flag,o_loadso4%name,"Column Load of Sulfate ","kg/m2") 1166 CALL histdef2d(iff,clef_stations(iff), & 1167 o_loadoa%flag,o_loadoa%name,"Column Load of Organic Aerosol ","kg/m2") 1168 CALL histdef2d(iff,clef_stations(iff), & 1169 o_loadbc%flag,o_loadbc%name,"Column Load of Black Carbon ","kg/m2") 1170 CALL histdef2d(iff,clef_stations(iff), & 1171 o_loadss%flag,o_loadss%name,"Column Load of Sea Salt ","kg/m2") 1172 CALL histdef2d(iff,clef_stations(iff), & 1173 o_loaddust%flag,o_loaddust%name,"Column Load of Dust ","kg/m2") 321 CALL histdef2d(iff,o_phis) 322 CALL histdef2d(iff,o_contfracOR) 323 CALL histdef2d(iff,o_aireTER) 324 CALL histdef2d(iff,o_flat) 325 CALL histdef2d(iff,o_slp) 326 CALL histdef2d(iff,o_tsol) 327 CALL histdef2d(iff,o_t2m) 328 CALL histdef2d(iff,o_t2m_min) 329 CALL histdef2d(iff,o_t2m_max) 330 CALL histdef2d(iff,o_wind10m) 331 CALL histdef2d(iff,o_wind10max) 332 CALL histdef2d(iff,o_sicf) 333 CALL histdef2d(iff,o_q2m) 334 CALL histdef2d(iff,o_ustar) 335 CALL histdef2d(iff,o_u10m) 336 CALL histdef2d(iff,o_v10m) 337 CALL histdef2d(iff,o_psol) 338 CALL histdef2d(iff,o_qsurf) 339 340 IF (.NOT. ok_veget) THEN 341 CALL histdef2d(iff,o_qsol) 342 ENDIF 343 CALL histdef2d(iff,o_ndayrain) 344 CALL histdef2d(iff,o_precip) 345 CALL histdef2d(iff,o_plul) 346 CALL histdef2d(iff,o_pluc) 347 CALL histdef2d(iff,o_snow) 348 CALL histdef2d(iff,o_msnow) 349 CALL histdef2d(iff,o_fsnow) 350 CALL histdef2d(iff,o_evap) 351 CALL histdef2d(iff,o_tops) 352 CALL histdef2d(iff,o_tops0) 353 CALL histdef2d(iff,o_topl) 354 CALL histdef2d(iff,o_topl0) 355 CALL histdef2d(iff,o_SWupTOA) 356 CALL histdef2d(iff,o_SWupTOAclr) 357 CALL histdef2d(iff,o_SWdnTOA) 358 CALL histdef2d(iff,o_SWdnTOAclr) 359 CALL histdef2d(iff,o_nettop) 360 CALL histdef2d(iff,o_SWup200) 361 CALL histdef2d(iff,o_SWup200clr) 362 CALL histdef2d(iff,o_SWdn200) 363 CALL histdef2d(iff,o_SWdn200clr) 364 CALL histdef2d(iff,o_LWup200) 365 CALL histdef2d(iff,o_LWup200clr) 366 CALL histdef2d(iff,o_LWdn200) 367 CALL histdef2d(iff,o_LWdn200clr) 368 CALL histdef2d(iff,o_sols) 369 CALL histdef2d(iff,o_sols0) 370 CALL histdef2d(iff,o_soll) 371 CALL histdef2d(iff,o_radsol) 372 CALL histdef2d(iff,o_soll0) 373 CALL histdef2d(iff,o_SWupSFC) 374 CALL histdef2d(iff,o_SWupSFCclr) 375 CALL histdef2d(iff,o_SWdnSFC) 376 CALL histdef2d(iff,o_SWdnSFCclr) 377 CALL histdef2d(iff,o_LWupSFC) 378 CALL histdef2d(iff,o_LWdnSFC) 379 CALL histdef2d(iff,o_LWupSFCclr) 380 CALL histdef2d(iff,o_LWdnSFCclr) 381 CALL histdef2d(iff,o_bils) 382 CALL histdef2d(iff,o_bils_ec) 383 CALL histdef2d(iff,o_bils_tke) 384 CALL histdef2d(iff,o_bils_diss) 385 CALL histdef2d(iff,o_bils_kinetic) 386 CALL histdef2d(iff,o_bils_enthalp) 387 CALL histdef2d(iff,o_bils_latent) 388 CALL histdef2d(iff,o_sens) 389 CALL histdef2d(iff,o_fder) 390 CALL histdef2d(iff,o_ffonte) 391 CALL histdef2d(iff,o_fqcalving) 392 CALL histdef2d(iff,o_fqfonte) 393 CALL histdef2d(iff,o_taux) 394 CALL histdef2d(iff,o_tauy) 395 396 DO nsrf = 1, nbsrf 397 CALL histdef2d(iff,o_pourc_srf(nsrf)) 398 CALL histdef2d(iff,o_fract_srf(nsrf)) 399 CALL histdef2d(iff, o_taux_srf(nsrf)) 400 CALL histdef2d(iff, o_tauy_srf(nsrf)) 401 CALL histdef2d(iff, o_tsol_srf(nsrf)) 402 CALL histdef2d(iff, o_evappot_srf(nsrf)) 403 CALL histdef2d(iff, o_ustar_srf(nsrf)) 404 CALL histdef2d(iff, o_u10m_srf(nsrf)) 405 CALL histdef2d(iff, o_evap_srf(nsrf)) 406 CALL histdef2d(iff, o_v10m_srf(nsrf)) 407 CALL histdef2d(iff, o_t2m_srf(nsrf)) 408 CALL histdef2d(iff, o_sens_srf(nsrf)) 409 CALL histdef2d(iff, o_lat_srf(nsrf)) 410 CALL histdef2d(iff, o_flw_srf(nsrf)) 411 CALL histdef2d(iff, o_fsw_srf(nsrf)) 412 CALL histdef2d(iff, o_wbils_srf(nsrf)) 413 CALL histdef2d(iff, o_wbilo_srf(nsrf)) 414 IF (iflag_pbl>1 ) then 415 CALL histdef2d(iff, o_tke_srf(nsrf)) 416 CALL histdef2d(iff, o_tke_max_srf(nsrf)) 417 ENDIF 418 419 CALL histdef2d(iff, o_albe_srf(nsrf)) 420 CALL histdef2d(iff, o_rugs_srf(nsrf)) 421 CALL histdef2d(iff, o_ages_srf(nsrf)) 422 END DO 423 424 IF (new_aod .AND. (.NOT. aerosol_couple)) THEN 425 IF (ok_ade.OR.ok_aie) THEN 426 CALL histdef2d(iff,o_od550aer) 427 CALL histdef2d(iff,o_od865aer) 428 CALL histdef2d(iff,o_absvisaer) 429 CALL histdef2d(iff,o_od550lt1aer) 430 CALL histdef2d(iff,o_sconcso4) 431 CALL histdef2d(iff,o_sconcoa) 432 CALL histdef2d(iff,o_sconcbc) 433 CALL histdef2d(iff,o_sconcss) 434 CALL histdef2d(iff,o_sconcdust) 435 CALL histdef3d(iff,o_concso4) 436 CALL histdef3d(iff,o_concoa) 437 CALL histdef3d(iff,o_concbc) 438 CALL histdef3d(iff,o_concss) 439 CALL histdef3d(iff,o_concdust) 440 CALL histdef2d(iff,o_loadso4) 441 CALL histdef2d(iff,o_loadoa) 442 CALL histdef2d(iff,o_loadbc) 443 CALL histdef2d(iff,o_loadss) 444 CALL histdef2d(iff,o_loaddust) 1174 445 !--STRAT AER 1175 ENDIF 1176 IF (ok_ade.OR.ok_aie.OR.flag_aerosol_strat) THEN 1177 DO naero = 1, naero_spc 1178 CALL histdef2d(iff,clef_stations(iff), & 1179 o_tausumaero(naero)%flag,o_tausumaero(naero)%name,"Aerosol Optical depth at 550 nm "//name_aero(naero),"1") 1180 END DO 1181 ENDIF 1182 ENDIF 1183 1184 IF (ok_ade) THEN 1185 CALL histdef2d(iff,clef_stations(iff), & 1186 o_topswad%flag,o_topswad%name, "ADE at TOA", "W/m2") 1187 CALL histdef2d(iff,clef_stations(iff), & 1188 o_topswad0%flag,o_topswad0%name, "ADE clear-sky at TOA", "W/m2") 1189 CALL histdef2d(iff,clef_stations(iff), & 1190 o_solswad%flag,o_solswad%name, "ADE at SRF", "W/m2") 1191 CALL histdef2d(iff,clef_stations(iff), & 1192 o_solswad0%flag,o_solswad0%name, "ADE clear-sky at SRF", "W/m2") 1193 1194 CALL histdef2d(iff,clef_stations(iff), & 1195 o_swtoaas_nat%flag,o_swtoaas_nat%name, "Natural aerosol radiative forcing all-sky at TOA", "W/m2") 1196 CALL histdef2d(iff,clef_stations(iff), & 1197 o_swsrfas_nat%flag,o_swsrfas_nat%name, "Natural aerosol radiative forcing all-sky at SRF", "W/m2") 1198 CALL histdef2d(iff,clef_stations(iff), & 1199 o_swtoacs_nat%flag,o_swtoacs_nat%name, "Natural aerosol radiative forcing clear-sky at TOA", "W/m2") 1200 CALL histdef2d(iff,clef_stations(iff), & 1201 o_swsrfcs_nat%flag,o_swsrfcs_nat%name, "Natural aerosol radiative forcing clear-sky at SRF", "W/m2") 1202 1203 CALL histdef2d(iff,clef_stations(iff), & 1204 o_swtoaas_ant%flag,o_swtoaas_ant%name, "Anthropogenic aerosol radiative forcing all-sky at TOA", "W/m2") 1205 CALL histdef2d(iff,clef_stations(iff), & 1206 o_swsrfas_ant%flag,o_swsrfas_ant%name, "Anthropogenic aerosol radiative forcing all-sky at SRF", "W/m2") 1207 CALL histdef2d(iff,clef_stations(iff), & 1208 o_swtoacs_ant%flag,o_swtoacs_ant%name, "Anthropogenic aerosol radiative forcing clear-sky at TOA", "W/m2") 1209 CALL histdef2d(iff,clef_stations(iff), & 1210 o_swsrfcs_ant%flag,o_swsrfcs_ant%name, "Anthropogenic aerosol radiative forcing clear-sky at SRF", "W/m2") 1211 1212 IF (.NOT. aerosol_couple) THEN 1213 CALL histdef2d(iff,clef_stations(iff), & 1214 o_swtoacf_nat%flag,o_swtoacf_nat%name, "Natural aerosol impact on cloud radiative forcing at TOA", "W/m2") 1215 CALL histdef2d(iff,clef_stations(iff), & 1216 o_swsrfcf_nat%flag,o_swsrfcf_nat%name, "Natural aerosol impact on cloud radiative forcing at SRF", "W/m2") 1217 CALL histdef2d(iff, clef_stations(iff), o_swtoacf_ant%flag, & 1218 o_swtoacf_ant%name, & 1219 "Anthropogenic aerosol impact on cloud radiative forcing at TOA", & 1220 "W/m2") 1221 CALL histdef2d(iff, clef_stations(iff), o_swsrfcf_ant%flag, & 1222 o_swsrfcf_ant%name, & 1223 "Anthropogenic aerosol impact on cloud radiative forcing at SRF", & 1224 "W/m2") 1225 CALL histdef2d(iff,clef_stations(iff), & 1226 o_swtoacf_zero%flag,o_swtoacf_zero%name, "Cloud radiative forcing (allsky-clearsky fluxes) at TOA", "W/m2") 1227 CALL histdef2d(iff,clef_stations(iff), & 1228 o_swsrfcf_zero%flag,o_swsrfcf_zero%name, "Cloud radiative forcing (allsky-clearsky fluxes) at SRF", "W/m2") 1229 ENDIF 1230 ENDIF 1231 1232 IF (ok_aie) THEN 1233 CALL histdef2d(iff,clef_stations(iff), & 1234 o_topswai%flag,o_topswai%name, "AIE at TOA", "W/m2") 1235 CALL histdef2d(iff,clef_stations(iff), & 1236 o_solswai%flag,o_solswai%name, "AIE at SFR", "W/m2") 1237 !Cloud droplet number concentration 1238 CALL histdef3d(iff,clef_stations(iff), & 1239 o_scdnc%flag,o_scdnc%name, "Cloud droplet number concentration","m-3") 1240 CALL histdef2d(iff,clef_stations(iff), & 1241 o_cldncl%flag,o_cldncl%name, "CDNC at top of liquid water cloud", "m-3") 1242 CALL histdef3d(iff,clef_stations(iff), & 1243 o_reffclws%flag,o_reffclws%name, "Stratiform Cloud Droplet Effective Radius (aerosol diags.)","m") 1244 CALL histdef3d(iff,clef_stations(iff), & 1245 o_reffclwc%flag,o_reffclwc%name, "Convective Cloud Droplet Effective Radius (aerosol diags.)","m") 1246 CALL histdef2d(iff,clef_stations(iff), & 1247 o_cldnvi%flag,o_cldnvi%name, "Column Integrated Cloud Droplet Number", "m-2") 1248 CALL histdef3d(iff,clef_stations(iff), & 1249 o_lcc3d%flag,o_lcc3d%name, "Cloud liquid fraction","1") 1250 CALL histdef3d(iff,clef_stations(iff), & 1251 o_lcc3dcon%flag,o_lcc3dcon%name, "Convective cloud liquid fraction","1") 1252 CALL histdef3d(iff,clef_stations(iff), & 1253 o_lcc3dstra%flag,o_lcc3dstra%name, "Stratiform cloud liquid fraction","1") 1254 CALL histdef2d(iff,clef_stations(iff), & 1255 o_lcc%flag,o_lcc%name, "Cloud liquid fraction at top of cloud","1") 1256 CALL histdef2d(iff,clef_stations(iff), & 1257 o_reffclwtop%flag,o_reffclwtop%name, "Droplet effective radius at top of liquid water cloud", "m") 1258 ENDIF 1259 1260 1261 CALL histdef2d(iff,clef_stations(iff), & 1262 o_alb1%flag,o_alb1%name, "Surface VIS albedo", "-") 1263 CALL histdef2d(iff,clef_stations(iff), & 1264 o_alb2%flag,o_alb2%name, "Surface Near IR albedo", "-") 1265 CALL histdef2d(iff,clef_stations(iff), & 1266 o_cdrm%flag,o_cdrm%name, "Momentum drag coef.", "-") 1267 CALL histdef2d(iff,clef_stations(iff), & 1268 o_cdrh%flag,o_cdrh%name, "Heat drag coef.", "-" ) 1269 CALL histdef2d(iff,clef_stations(iff), & 1270 o_cldl%flag,o_cldl%name, "Low-level cloudiness", "-") 1271 CALL histdef2d(iff,clef_stations(iff), & 1272 o_cldm%flag,o_cldm%name, "Mid-level cloudiness", "-") 1273 CALL histdef2d(iff,clef_stations(iff), & 1274 o_cldh%flag,o_cldh%name, "High-level cloudiness", "-") 1275 CALL histdef2d(iff,clef_stations(iff), & 1276 o_cldt%flag,o_cldt%name, "Total cloudiness", "-") 1277 CALL histdef2d(iff,clef_stations(iff), & 1278 o_cldq%flag,o_cldq%name, "Cloud liquid water path", "kg/m2") 1279 CALL histdef2d(iff,clef_stations(iff), & 1280 o_lwp%flag,o_lwp%name, "Cloud water path", "kg/m2") 1281 CALL histdef2d(iff,clef_stations(iff), & 1282 o_iwp%flag,o_iwp%name, "Cloud ice water path", "kg/m2" ) 1283 CALL histdef2d(iff,clef_stations(iff), & 1284 o_ue%flag,o_ue%name, "Zonal energy transport", "-") 1285 CALL histdef2d(iff,clef_stations(iff), & 1286 o_ve%flag,o_ve%name, "Merid energy transport", "-") 1287 CALL histdef2d(iff,clef_stations(iff), & 1288 o_uq%flag,o_uq%name, "Zonal humidity transport", "-") 1289 CALL histdef2d(iff,clef_stations(iff), & 1290 o_vq%flag,o_vq%name, "Merid humidity transport", "-") 1291 1292 IF(iflag_con.GE.3) THEN ! sb 1293 CALL histdef2d(iff,clef_stations(iff), & 1294 o_cape%flag,o_cape%name, "Conv avlbl pot ener", "J/kg") 1295 CALL histdef2d(iff,clef_stations(iff), & 1296 o_pbase%flag,o_pbase%name, "Cld base pressure", "Pa") 1297 CALL histdef2d(iff,clef_stations(iff), & 1298 o_ptop%flag,o_ptop%name, "Cld top pressure", "Pa") 1299 CALL histdef2d(iff,clef_stations(iff), & 1300 o_fbase%flag,o_fbase%name, "Cld base mass flux", "kg/m2/s") 1301 if (iflag_con /= 30) then 1302 CALL histdef2d(iff,clef_stations(iff), & 1303 o_plcl%flag,o_plcl%name, "Lifting Condensation Level", "hPa") 1304 CALL histdef2d(iff,clef_stations(iff), & 1305 o_plfc%flag,o_plfc%name, "Level of Free Convection", "hPa") 1306 CALL histdef2d(iff,clef_stations(iff), & 1307 o_wbeff%flag,o_wbeff%name, "Conv. updraft velocity at LFC (<100)", "m/s") 1308 end if 1309 IF (.NOT.clef_stations(iff)) THEN 1310 ! 1311 !IM: there is no way to have one single value in a netcdf file 1312 ! 1313 type_ecri(1) = 't_max(X)' 1314 type_ecri(2) = 't_max(X)' 1315 type_ecri(3) = 't_max(X)' 1316 type_ecri(4) = 't_max(X)' 1317 type_ecri(5) = 't_max(X)' 1318 type_ecri(6) = 't_max(X)' 1319 CALL histdef2d(iff,clef_stations(iff), & 1320 o_cape_max%flag,o_cape_max%name, "CAPE max.", "J/kg") 1321 ENDIF 1322 type_ecri(:) = type_ecri_files(:) 1323 CALL histdef3d(iff,clef_stations(iff), & 1324 o_upwd%flag,o_upwd%name, "saturated updraft", "kg/m2/s") 1325 CALL histdef3d(iff,clef_stations(iff), & 1326 o_Ma%flag,o_Ma%name, "undilute adiab updraft", "kg/m2/s") 1327 CALL histdef3d(iff,clef_stations(iff), & 1328 o_dnwd%flag,o_dnwd%name, "saturated downdraft", "kg/m2/s") 1329 CALL histdef3d(iff,clef_stations(iff), & 1330 o_dnwd0%flag,o_dnwd0%name, "unsat. downdraft", "kg/m2/s") 1331 CALL histdef3d(iff,clef_stations(iff), & 1332 o_mc%flag,o_mc%name, "Convective mass flux", "kg/m2/s") 1333 type_ecri(1) = 'inst(X)' 1334 type_ecri(2) = 'inst(X)' 1335 type_ecri(3) = 'inst(X)' 1336 type_ecri(4) = 'inst(X)' 1337 type_ecri(5) = 'inst(X)' 1338 type_ecri(6) = 'inst(X)' 1339 CALL histdef2d(iff,clef_stations(iff), & 1340 o_ftime_con%flag,o_ftime_con%name, "Fraction of time convection Occurs", " ") 1341 type_ecri(:) = type_ecri_files(:) 1342 ENDIF !iflag_con .GE. 3 1343 1344 CALL histdef2d(iff,clef_stations(iff), & 1345 o_prw%flag,o_prw%name, "Precipitable water", "kg/m2") 1346 CALL histdef2d(iff,clef_stations(iff), & 1347 o_s_pblh%flag,o_s_pblh%name, "Boundary Layer Height", "m") 1348 CALL histdef2d(iff,clef_stations(iff), & 1349 o_s_pblt%flag,o_s_pblt%name, "t at Boundary Layer Height", "K") 1350 CALL histdef2d(iff,clef_stations(iff), & 1351 o_s_lcl%flag,o_s_lcl%name, "Condensation level", "m") 1352 CALL histdef2d(iff,clef_stations(iff), & 1353 o_s_therm%flag,o_s_therm%name, "Exces du thermique", "K") 446 ENDIF 447 IF (ok_ade.OR.ok_aie.OR.flag_aerosol_strat) THEN 448 DO naero = 1, naero_spc 449 CALL histdef2d(iff, o_tausumaero(naero)) 450 END DO 451 ENDIF 452 ENDIF 453 454 IF (ok_ade) THEN 455 CALL histdef2d(iff,o_topswad) 456 CALL histdef2d(iff,o_topswad0) 457 CALL histdef2d(iff,o_solswad) 458 CALL histdef2d(iff,o_solswad0) 459 CALL histdef2d(iff,o_swtoaas_nat) 460 CALL histdef2d(iff,o_swsrfas_nat) 461 CALL histdef2d(iff,o_swtoacs_nat) 462 CALL histdef2d(iff,o_swsrfcs_nat) 463 CALL histdef2d(iff,o_swtoaas_ant) 464 CALL histdef2d(iff,o_swsrfas_ant) 465 CALL histdef2d(iff,o_swtoacs_ant) 466 CALL histdef2d(iff,o_swsrfcs_ant) 467 468 IF (.NOT. aerosol_couple) THEN 469 CALL histdef2d(iff,o_swtoacf_nat) 470 CALL histdef2d(iff,o_swsrfcf_nat) 471 CALL histdef2d(iff,o_swtoacf_ant) 472 CALL histdef2d(iff,o_swsrfcf_ant) 473 CALL histdef2d(iff,o_swtoacf_zero) 474 CALL histdef2d(iff,o_swsrfcf_zero) 475 ENDIF 476 ENDIF 477 478 IF (ok_aie) THEN 479 CALL histdef2d(iff,o_topswai) 480 CALL histdef2d(iff,o_solswai) 481 !Cloud droplet number concentration 482 CALL histdef3d(iff,o_scdnc) 483 CALL histdef2d(iff,o_cldncl) 484 CALL histdef3d(iff,o_reffclws) 485 CALL histdef3d(iff,o_reffclwc) 486 CALL histdef2d(iff,o_cldnvi) 487 CALL histdef3d(iff,o_lcc3d) 488 CALL histdef3d(iff,o_lcc3dcon) 489 CALL histdef3d(iff,o_lcc3dstra) 490 CALL histdef2d(iff,o_lcc) 491 CALL histdef2d(iff,o_reffclwtop) 492 ENDIF 493 CALL histdef2d(iff,o_alb1) 494 CALL histdef2d(iff,o_alb2) 495 CALL histdef2d(iff,o_cdrm) 496 CALL histdef2d(iff,o_cdrh) 497 CALL histdef2d(iff,o_cldl) 498 CALL histdef2d(iff,o_cldm) 499 CALL histdef2d(iff,o_cldh) 500 CALL histdef2d(iff,o_cldt) 501 CALL histdef2d(iff,o_cldq) 502 CALL histdef2d(iff,o_lwp) 503 CALL histdef2d(iff,o_iwp) 504 CALL histdef2d(iff,o_ue) 505 CALL histdef2d(iff,o_ve) 506 CALL histdef2d(iff,o_uq) 507 CALL histdef2d(iff,o_vq) 508 509 IF(iflag_con.GE.3) THEN ! sb 510 CALL histdef2d(iff,o_cape) 511 CALL histdef2d(iff,o_pbase) 512 CALL histdef2d(iff,o_ptop) 513 CALL histdef2d(iff,o_fbase) 514 IF (iflag_con /= 30) THEN 515 CALL histdef2d(iff,o_plcl) 516 CALL histdef2d(iff,o_plfc) 517 CALL histdef2d(iff,o_wbeff) 518 ENDIF 519 CALL histdef2d(iff,o_cape_max) 520 CALL histdef3d(iff,o_upwd) 521 CALL histdef3d(iff,o_Ma) 522 CALL histdef3d(iff,o_dnwd) 523 CALL histdef3d(iff,o_dnwd0) 524 CALL histdef3d(iff,o_mc) 525 CALL histdef2d(iff,o_ftime_con) 526 ENDIF !iflag_con .GE. 3 527 CALL histdef2d(iff,o_prw) 528 CALL histdef2d(iff,o_s_pblh) 529 CALL histdef2d(iff,o_s_pblt) 530 CALL histdef2d(iff,o_s_lcl) 531 CALL histdef2d(iff,o_s_therm) 1354 532 !IM : Les champs suivants (s_oliqCL, s_cteiCL, s_trmb1, s_trmb2, s_trmb3) ne sont pas definis dans HBTM.F 1355 !CALL histdef2d(iff, clef_stations(iff),&533 !CALL histdef2d(iff, & 1356 534 !o_s_capCL%flag,o_s_capCL%name, "Conv avlbl pot enerfor ABL", "J/m2" ) 1357 !CALL histdef2d(iff, clef_stations(iff),&535 !CALL histdef2d(iff, & 1358 536 !o_s_oliqCL%flag,o_s_oliqCL%name, "Liq Water in BL", "kg/m2") 1359 !CALL histdef2d(iff, clef_stations(iff),&537 !CALL histdef2d(iff, & 1360 538 !o_s_cteiCL%flag,o_s_cteiCL%name, "Instability criteria(ABL)", "K") 1361 !CALL histdef2d(iff, clef_stations(iff),&539 !CALL histdef2d(iff, & 1362 540 !o_s_trmb1%flag,o_s_trmb1%name, "deep_cape(HBTM2)", "J/m2") 1363 !CALL histdef2d(iff, clef_stations(iff),&541 !CALL histdef2d(iff, & 1364 542 !o_s_trmb2%flag,o_s_trmb2%name, "inhibition (HBTM2)", "J/m2") 1365 !CALL histdef2d(iff, clef_stations(iff),&543 !CALL histdef2d(iff, & 1366 544 !o_s_trmb3%flag,o_s_trmb3%name, "Point Omega (HBTM2)", "m") 1367 545 1368 546 ! Champs interpolles sur des niveaux de pression 1369 547 1370 type_ecri(1) = 'inst(X)'1371 type_ecri(2) = 'inst(X)'1372 type_ecri(3) = 'inst(X)'1373 type_ecri(4) = 'inst(X)'1374 type_ecri(5) = 'inst(X)'1375 type_ecri(6) = 'inst(X)'1376 1377 548 ! Attention a reverifier 1378 549 1379 1380 1381 1382 550 ilev=0 551 DO k=1, nlevSTD 552 bb2=clevSTD(k) 553 IF(bb2.EQ."850".OR.bb2.EQ."700".OR.bb2.EQ."500".OR.bb2.EQ."200" & 1383 554 .OR.bb2.EQ."100".OR.bb2.EQ."50".OR.bb2.EQ."10")THEN 1384 ilev=ilev+1 1385 ! print*,'ilev k bb2 flag name ',ilev,k, bb2,o_uSTDlevs(ilev)%flag,o_uSTDlevs(ilev)%name 1386 CALL histdef2d(iff,clef_stations(iff), & 1387 o_uSTDlevs(ilev)%flag,o_uSTDlevs(ilev)%name,"Zonal wind "//bb2//"hPa", "m/s") 1388 CALL histdef2d(iff,clef_stations(iff), & 1389 o_vSTDlevs(ilev)%flag,o_vSTDlevs(ilev)%name,"Meridional wind "//bb2//"hPa", "m/s") 1390 CALL histdef2d(iff,clef_stations(iff), & 1391 o_wSTDlevs(ilev)%flag,o_wSTDlevs(ilev)%name,"Vertical wind "//bb2//"hPa", "Pa/s") 1392 CALL histdef2d(iff,clef_stations(iff), & 1393 o_zSTDlevs(ilev)%flag,o_zSTDlevs(ilev)%name,"Geopotential height "//bb2//"hPa", "m") 1394 CALL histdef2d(iff,clef_stations(iff), & 1395 o_qSTDlevs(ilev)%flag,o_qSTDlevs(ilev)%name,"Specific humidity "//bb2//"hPa", "kg/kg" ) 1396 CALL histdef2d(iff,clef_stations(iff), & 1397 o_tSTDlevs(ilev)%flag,o_tSTDlevs(ilev)%name,"Temperature "//bb2//"hPa", "K") 1398 ENDIF !(bb2.EQ."850".OR.bb2.EQ."700".OR."500".OR.bb2.EQ."200".OR.bb2.EQ."50".OR.bb2.EQ."10") 1399 ENDDO 1400 type_ecri(:) = type_ecri_files(:) 1401 1402 CALL histdef2d(iff,clef_stations(iff), & 1403 o_t_oce_sic%flag,o_t_oce_sic%name, "Temp mixte oce-sic", "K") 1404 1405 IF (type_ocean=='slab') & 1406 CALL histdef2d(iff,clef_stations(iff), & 1407 o_slab_bils%flag, o_slab_bils%name,"Bilan au sol sur ocean slab", "W/m2") 1408 1409 ! Couplage conv-CL 1410 IF (iflag_con.GE.3) THEN 1411 IF (iflag_coupl>=1) THEN 1412 CALL histdef2d(iff,clef_stations(iff), & 1413 o_ale_bl%flag,o_ale_bl%name, "ALE BL", "m2/s2") 1414 CALL histdef2d(iff,clef_stations(iff), & 1415 o_alp_bl%flag,o_alp_bl%name, "ALP BL", "m2/s2") 1416 ENDIF 1417 ENDIF !(iflag_con.GE.3) 1418 1419 CALL histdef2d(iff,clef_stations(iff), & 1420 o_weakinv%flag,o_weakinv%name, "Weak inversion", "-") 1421 CALL histdef2d(iff,clef_stations(iff), & 1422 o_dthmin%flag,o_dthmin%name, "dTheta mini", "K/m") 1423 CALL histdef2d(iff,clef_stations(iff), & 1424 o_rh2m%flag,o_rh2m%name, "Relative humidity at 2m", "%" ) 1425 1426 IF (.NOT.clef_stations(iff)) THEN 1427 ! 1428 !IM: there is no way to have one single value in a netcdf file 1429 ! 1430 type_ecri(1) = 't_min(X)' 1431 type_ecri(2) = 't_min(X)' 1432 type_ecri(3) = 't_min(X)' 1433 type_ecri(4) = 't_min(X)' 1434 type_ecri(5) = 't_min(X)' 1435 type_ecri(6) = 't_min(X)' 1436 CALL histdef2d(iff,clef_stations(iff),o_rh2m_min%flag,o_rh2m_min%name, "Min Relative humidity at 2m", "%" ) 1437 type_ecri(1) = 't_max(X)' 1438 type_ecri(2) = 't_max(X)' 1439 type_ecri(3) = 't_max(X)' 1440 type_ecri(4) = 't_max(X)' 1441 type_ecri(5) = 't_max(X)' 1442 type_ecri(6) = 't_max(X)' 1443 CALL histdef2d(iff,clef_stations(iff),o_rh2m_max%flag,o_rh2m_max%name, "Max Relative humidity at 2m", "%" ) 1444 ENDIF 1445 1446 type_ecri(:) = type_ecri_files(:) 1447 CALL histdef2d(iff,clef_stations(iff),o_qsat2m%flag,o_qsat2m%name, "Saturant humidity at 2m", "%") 1448 CALL histdef2d(iff,clef_stations(iff),o_tpot%flag,o_tpot%name, "Surface air potential temperature", "K") 1449 CALL histdef2d(iff,clef_stations(iff), & 1450 o_tpote%flag,o_tpote%name, "Surface air equivalent potential temperature", "K") 1451 CALL histdef2d(iff,clef_stations(iff),o_SWnetOR%flag,o_SWnetOR%name, "Sfce net SW radiation OR", "W/m2") 1452 CALL histdef2d(iff,clef_stations(iff),o_SWdownOR%flag,o_SWdownOR%name, "Sfce incident SW radiation OR", "W/m2") 1453 CALL histdef2d(iff,clef_stations(iff),o_LWdownOR%flag,o_LWdownOR%name, "Sfce incident LW radiation OR", "W/m2") 1454 CALL histdef2d(iff,clef_stations(iff),o_snowl%flag,o_snowl%name, "Solid Large-scale Precip.", "kg/(m2*s)") 1455 1456 CALL histdef2d(iff,clef_stations(iff),o_solldown%flag,o_solldown%name, "Down. IR rad. at surface", "W/m2") 1457 CALL histdef2d(iff,clef_stations(iff),o_dtsvdfo%flag,o_dtsvdfo%name, "Boundary-layer dTs(o)", "K/s") 1458 CALL histdef2d(iff,clef_stations(iff),o_dtsvdft%flag,o_dtsvdft%name, "Boundary-layer dTs(t)", "K/s") 1459 CALL histdef2d(iff,clef_stations(iff),o_dtsvdfg%flag,o_dtsvdfg%name, "Boundary-layer dTs(g)", "K/s") 1460 CALL histdef2d(iff,clef_stations(iff),o_dtsvdfi%flag,o_dtsvdfi%name, "Boundary-layer dTs(g)", "K/s") 1461 CALL histdef2d(iff,clef_stations(iff),o_rugs%flag,o_rugs%name, "rugosity", "-" ) 555 ilev=ilev+1 556 ! print*,'ilev k bb2 flag name ',ilev,k, bb2,o_uSTDlevs(ilev)%flag,o_uSTDlevs(ilev)%name 557 CALL histdef2d(iff,o_uSTDlevs(ilev)) 558 CALL histdef2d(iff,o_vSTDlevs(ilev)) 559 CALL histdef2d(iff,o_wSTDlevs(ilev)) 560 CALL histdef2d(iff,o_zSTDlevs(ilev)) 561 CALL histdef2d(iff,o_qSTDlevs(ilev)) 562 CALL histdef2d(iff,o_tSTDlevs(ilev)) 563 ENDIF !(bb2.EQ."850".OR.bb2.EQ."700".OR."500".OR.bb2.EQ."200".OR.bb2.EQ."50".OR.bb2.EQ."10") 564 ENDDO 565 566 CALL histdef2d(iff,o_t_oce_sic) 567 568 IF (type_ocean=='slab') THEN 569 CALL histdef2d(iff,o_slab_bils) 570 ENDIF 571 572 ! Couplage conv-CL 573 IF (iflag_con.GE.3) THEN 574 IF (iflag_coupl>=1) THEN 575 CALL histdef2d(iff,o_ale_bl) 576 CALL histdef2d(iff,o_alp_bl) 577 ENDIF 578 ENDIF !(iflag_con.GE.3) 579 580 CALL histdef2d(iff,o_weakinv) 581 CALL histdef2d(iff,o_dthmin) 582 583 CALL histdef2d(iff,o_rh2m) 584 CALL histdef2d(iff,o_rh2m_min) 585 CALL histdef2d(iff,o_rh2m_max) 586 587 CALL histdef2d(iff,o_qsat2m) 588 CALL histdef2d(iff,o_tpot) 589 CALL histdef2d(iff,o_tpote) 590 CALL histdef2d(iff,o_SWnetOR) 591 CALL histdef2d(iff,o_SWdownOR) 592 CALL histdef2d(iff,o_LWdownOR) 593 CALL histdef2d(iff,o_snowl) 594 CALL histdef2d(iff,o_solldown) 595 CALL histdef2d(iff,o_dtsvdfo) 596 CALL histdef2d(iff,o_dtsvdft) 597 CALL histdef2d(iff,o_dtsvdfg) 598 CALL histdef2d(iff,o_dtsvdfi) 599 CALL histdef2d(iff,o_rugs) 1462 600 1463 601 ! Champs 3D: 1464 CALL histdef3d(iff,clef_stations(iff),o_ec550aer%flag,o_ec550aer%name, "Extinction at 550nm", "m^-1") 1465 CALL histdef3d(iff,clef_stations(iff),o_lwcon%flag,o_lwcon%name, "Cloud liquid water content", "kg/kg") 1466 CALL histdef3d(iff,clef_stations(iff),o_iwcon%flag,o_iwcon%name, "Cloud ice water content", "kg/kg") 1467 CALL histdef3d(iff,clef_stations(iff),o_temp%flag,o_temp%name, "Air temperature", "K" ) 1468 CALL histdef3d(iff,clef_stations(iff),o_theta%flag,o_theta%name, "Potential air temperature", "K" ) 1469 CALL histdef3d(iff,clef_stations(iff),o_ovap%flag,o_ovap%name, "Specific humidity", "kg/kg" ) 1470 CALL histdef3d(iff,clef_stations(iff),o_oliq%flag,o_oliq%name, "Condensed water", "kg/kg" ) 1471 CALL histdef3d(iff,clef_stations(iff), & 1472 o_ovapinit%flag,o_ovapinit%name, "Specific humidity (begin of timestep)", "kg/kg" ) 1473 CALL histdef3d(iff,clef_stations(iff), & 1474 o_geop%flag,o_geop%name, "Geopotential height", "m2/s2") 1475 CALL histdef3d(iff,clef_stations(iff), & 1476 o_vitu%flag,o_vitu%name, "Zonal wind", "m/s" ) 1477 CALL histdef3d(iff,clef_stations(iff), & 1478 o_vitv%flag,o_vitv%name, "Meridional wind", "m/s" ) 1479 CALL histdef3d(iff,clef_stations(iff), & 1480 o_vitw%flag,o_vitw%name, "Vertical wind", "Pa/s" ) 1481 CALL histdef3d(iff,clef_stations(iff), & 1482 o_pres%flag,o_pres%name, "Air pressure", "Pa" ) 1483 CALL histdef3d(iff,clef_stations(iff), & 1484 o_paprs%flag,o_paprs%name, "Air pressure Inter-Couches", "Pa" ) 1485 CALL histdef3d(iff,clef_stations(iff), & 1486 o_mass%flag,o_mass%name, "Masse Couches", "kg/m2" ) 1487 CALL histdef3d(iff,clef_stations(iff), & 1488 o_zfull%flag,o_zfull%name, "Altitude of full pressure levels", "m" ) 1489 CALL histdef3d(iff,clef_stations(iff), & 1490 o_zhalf%flag,o_zhalf%name, "Altitude of half pressure levels", "m" ) 1491 CALL histdef3d(iff,clef_stations(iff), & 1492 o_rneb%flag,o_rneb%name, "Cloud fraction", "-") 1493 CALL histdef3d(iff,clef_stations(iff), & 1494 o_rnebcon%flag,o_rnebcon%name, "Convective Cloud Fraction", "-") 1495 CALL histdef3d(iff,clef_stations(iff), & 1496 o_rnebls%flag,o_rnebls%name, "LS Cloud fraction", "-") 1497 CALL histdef3d(iff,clef_stations(iff), & 1498 o_rhum%flag,o_rhum%name, "Relative humidity", "-") 1499 CALL histdef3d(iff,clef_stations(iff), & 1500 o_ozone%flag,o_ozone%name, "Ozone mole fraction", "-") 1501 if (read_climoz == 2) & 1502 CALL histdef3d(iff,clef_stations(iff), & 1503 o_ozone_light%flag,o_ozone_light%name, & 1504 "Daylight ozone mole fraction", "-") 1505 CALL histdef3d(iff,clef_stations(iff), & 1506 o_dtphy%flag,o_dtphy%name, "Physics dT", "K/s") 1507 CALL histdef3d(iff,clef_stations(iff), & 1508 o_dqphy%flag,o_dqphy%name, "Physics dQ", "(kg/kg)/s") 1509 CALL histdef3d(iff,clef_stations(iff), & 1510 o_cldtau%flag,o_cldtau%name, "Cloud optical thickness", "1") 1511 CALL histdef3d(iff,clef_stations(iff), & 1512 o_cldemi%flag,o_cldemi%name, "Cloud optical emissivity", "1") 1513 !IM: bug ?? dimensionnement variables (klon,klev+1) pmflxr, pmflxs, prfl, psfl 1514 CALL histdef3d(iff,clef_stations(iff), & 1515 o_pr_con_l%flag,o_pr_con_l%name, "Convective precipitation lic", " ") 1516 CALL histdef3d(iff,clef_stations(iff), & 1517 o_pr_con_i%flag,o_pr_con_i%name, "Convective precipitation ice", " ") 1518 CALL histdef3d(iff,clef_stations(iff), & 1519 o_pr_lsc_l%flag,o_pr_lsc_l%name, "Large scale precipitation lic", " ") 1520 CALL histdef3d(iff,clef_stations(iff), & 1521 o_pr_lsc_i%flag,o_pr_lsc_i%name, "Large scale precipitation ice", " ") 1522 !Cloud droplet effective radius 1523 CALL histdef3d(iff,clef_stations(iff), & 1524 o_re%flag,o_re%name, "Cloud droplet effective radius","um") 1525 CALL histdef3d(iff,clef_stations(iff), & 1526 o_fl%flag,o_fl%name, "Denominator of Cloud droplet effective radius"," ") 1527 !FH Sorties pour la couche limite 1528 if (iflag_pbl>1) then 1529 CALL histdef3d(iff,clef_stations(iff), & 1530 o_tke%flag,o_tke%name, "TKE", "m2/s2") 1531 IF (.NOT.clef_stations(iff)) THEN 1532 ! 1533 !IM: there is no way to have one single value in a netcdf file 1534 ! 1535 type_ecri(1) = 't_max(X)' 1536 type_ecri(2) = 't_max(X)' 1537 type_ecri(3) = 't_max(X)' 1538 type_ecri(4) = 't_max(X)' 1539 type_ecri(5) = 't_max(X)' 1540 type_ecri(6) = 't_max(X)' 1541 CALL histdef3d(iff,clef_stations(iff), & 1542 o_tke_max%flag,o_tke_max%name, "TKE max", "m2/s2") 1543 ENDIF 1544 type_ecri(:) = type_ecri_files(:) 1545 endif 1546 1547 CALL histdef3d(iff,clef_stations(iff), & 1548 o_kz%flag,o_kz%name, "Kz melange", "m2/s") 1549 IF (.NOT.clef_stations(iff)) THEN 1550 ! 1551 !IM: there is no way to have one single value in a netcdf file 1552 ! 1553 type_ecri(1) = 't_max(X)' 1554 type_ecri(2) = 't_max(X)' 1555 type_ecri(3) = 't_max(X)' 1556 type_ecri(4) = 't_max(X)' 1557 type_ecri(5) = 't_max(X)' 1558 type_ecri(6) = 't_max(X)' 1559 CALL histdef3d(iff,clef_stations(iff), & 1560 o_kz_max%flag,o_kz_max%name, "Kz melange max", "m2/s" ) 1561 ENDIF 1562 type_ecri(:) = type_ecri_files(:) 1563 CALL histdef3d(iff,clef_stations(iff), & 1564 o_clwcon%flag,o_clwcon%name, "Convective Cloud Liquid water content", "kg/kg") 1565 CALL histdef3d(iff,clef_stations(iff), & 1566 o_dtdyn%flag,o_dtdyn%name, "Dynamics dT", "K/s") 1567 CALL histdef3d(iff,clef_stations(iff), & 1568 o_dqdyn%flag,o_dqdyn%name, "Dynamics dQ", "(kg/kg)/s") 1569 CALL histdef3d(iff,clef_stations(iff), & 1570 o_dudyn%flag,o_dudyn%name, "Dynamics dU", "m/s2") 1571 CALL histdef3d(iff,clef_stations(iff), & 1572 o_dvdyn%flag,o_dvdyn%name, "Dynamics dV", "m/s2") 1573 CALL histdef3d(iff,clef_stations(iff), & 1574 o_dtcon%flag,o_dtcon%name, "Convection dT", "K/s") 1575 CALL histdef3d(iff,clef_stations(iff), & 1576 o_ducon%flag,o_ducon%name, "Convection du", "m/s2") 1577 CALL histdef3d(iff,clef_stations(iff), & 1578 o_dvcon%flag,o_dvcon%name, "Convection dv", "m/s2") 1579 CALL histdef3d(iff,clef_stations(iff), & 1580 o_dqcon%flag,o_dqcon%name, "Convection dQ", "(kg/kg)/s") 1581 1582 ! Wakes 1583 IF(iflag_con.EQ.3) THEN 1584 IF (iflag_wake >= 1) THEN 1585 CALL histdef2d(iff,clef_stations(iff), & 1586 o_ale_wk%flag,o_ale_wk%name, "ALE WK", "m2/s2") 1587 CALL histdef2d(iff,clef_stations(iff), & 1588 o_alp_wk%flag,o_alp_wk%name, "ALP WK", "m2/s2") 1589 CALL histdef2d(iff,clef_stations(iff), & 1590 o_ale%flag,o_ale%name, "ALE", "m2/s2") 1591 CALL histdef2d(iff,clef_stations(iff), & 1592 o_alp%flag,o_alp%name, "ALP", "W/m2") 1593 CALL histdef2d(iff,clef_stations(iff),o_cin%flag,o_cin%name, "Convective INhibition", "m2/s2") 1594 CALL histdef2d(iff,clef_stations(iff),o_wape%flag,o_WAPE%name, "WAPE", "m2/s2") 1595 CALL histdef2d(iff,clef_stations(iff),o_wake_h%flag,o_wake_h%name, "wake_h", "-") 1596 CALL histdef2d(iff,clef_stations(iff),o_wake_s%flag,o_wake_s%name, "wake_s", "-") 1597 CALL histdef3d(iff,clef_stations(iff),o_dtwak%flag,o_dtwak%name, "Wake dT", "K/s") 1598 CALL histdef3d(iff,clef_stations(iff),o_dqwak%flag,o_dqwak%name, "Wake dQ", "(kg/kg)/s") 1599 CALL histdef3d(iff,clef_stations(iff),o_wake_deltat%flag,o_wake_deltat%name, "wake_deltat", " ") 1600 CALL histdef3d(iff,clef_stations(iff),o_wake_deltaq%flag,o_wake_deltaq%name, "wake_deltaq", " ") 1601 CALL histdef3d(iff,clef_stations(iff),o_wake_omg%flag,o_wake_omg%name, "wake_omg", " ") 1602 ENDIF 1603 !!! RomP CALL histdef3d(iff,clef_stations(iff),o_Vprecip%flag,o_Vprecip%name, "precipitation vertical profile", "-") 1604 CALL histdef3d(iff,clef_stations(iff),o_ftd%flag,o_ftd%name, "tend temp due aux descentes precip", "-") 1605 CALL histdef3d(iff,clef_stations(iff),o_fqd%flag,o_fqd%name,"tend vap eau due aux descentes precip", "-") 1606 ENDIF !(iflag_con.EQ.3) 1607 1608 IF(iflag_con.GE.3) THEN ! RomP >>> 1609 CALL histdef3d(iff,clef_stations(iff),o_wdtrainA%flag,o_wdtrainA%name, "precipitation from AA", "-") 1610 CALL histdef3d(iff,clef_stations(iff),o_wdtrainM%flag,o_wdtrainM%name, "precipitation from mixture", "-") 1611 CALL histdef3d(iff,clef_stations(iff),o_Vprecip%flag,o_Vprecip%name, "precipitation vertical profile", "-") 1612 ENDIF !(iflag_con.GE.3) ! <<< RomP 602 CALL histdef3d(iff,o_ec550aer) 603 CALL histdef3d(iff,o_lwcon) 604 CALL histdef3d(iff,o_iwcon) 605 CALL histdef3d(iff,o_temp) 606 CALL histdef3d(iff,o_theta) 607 CALL histdef3d(iff,o_ovap) 608 CALL histdef3d(iff,o_oliq) 609 CALL histdef3d(iff,o_ovapinit) 610 CALL histdef3d(iff,o_geop) 611 CALL histdef3d(iff,o_vitu) 612 CALL histdef3d(iff,o_vitv) 613 CALL histdef3d(iff,o_vitw) 614 CALL histdef3d(iff,o_pres) 615 CALL histdef3d(iff,o_paprs) 616 CALL histdef3d(iff,o_mass) 617 CALL histdef3d(iff,o_zfull) 618 CALL histdef3d(iff,o_zhalf) 619 CALL histdef3d(iff,o_rneb) 620 CALL histdef3d(iff,o_rnebcon) 621 CALL histdef3d(iff,o_rnebls) 622 CALL histdef3d(iff,o_rhum) 623 CALL histdef3d(iff,o_ozone) 624 625 IF (read_climoz == 2) THEN 626 CALL histdef3d(iff,o_ozone_light) 627 END IF 628 629 CALL histdef3d(iff,o_dtphy) 630 CALL histdef3d(iff,o_dqphy) 631 CALL histdef3d(iff,o_cldtau) 632 CALL histdef3d(iff,o_cldemi) 633 !IM: bug ?? dimensionnement variables (klon,klev+1) pmflxr, pmflxs, prfl, psfl 634 CALL histdef3d(iff,o_pr_con_l) 635 CALL histdef3d(iff,o_pr_con_i) 636 CALL histdef3d(iff,o_pr_lsc_l) 637 CALL histdef3d(iff,o_pr_lsc_i) 638 !Cloud droplet effective radius 639 CALL histdef3d(iff,o_re) 640 CALL histdef3d(iff,o_fl) 641 !FH Sorties pour la couche limite 642 IF (iflag_pbl>1) THEN 643 CALL histdef3d(iff,o_tke) 644 CALL histdef3d(iff,o_tke_max) 645 ENDIF 646 CALL histdef3d(iff,o_kz) 647 CALL histdef3d(iff,o_kz_max) 648 CALL histdef3d(iff,o_clwcon) 649 CALL histdef3d(iff,o_dtdyn) 650 CALL histdef3d(iff,o_dqdyn) 651 CALL histdef3d(iff,o_dudyn) 652 CALL histdef3d(iff,o_dvdyn) 653 CALL histdef3d(iff,o_dtcon) 654 CALL histdef3d(iff,o_ducon) 655 CALL histdef3d(iff,o_dvcon) 656 CALL histdef3d(iff,o_dqcon) 657 658 ! Wakes 659 IF(iflag_con.EQ.3) THEN 660 IF (iflag_wake >= 1) THEN 661 CALL histdef2d(iff,o_ale_wk) 662 CALL histdef2d(iff,o_alp_wk) 663 CALL histdef2d(iff,o_ale) 664 CALL histdef2d(iff,o_alp) 665 CALL histdef2d(iff,o_cin) 666 CALL histdef2d(iff,o_wape) 667 CALL histdef2d(iff,o_wake_h) 668 CALL histdef2d(iff,o_wake_s) 669 CALL histdef3d(iff,o_dtwak) 670 CALL histdef3d(iff,o_dqwak) 671 CALL histdef3d(iff,o_wake_deltat) 672 CALL histdef3d(iff,o_wake_deltaq) 673 CALL histdef3d(iff,o_wake_omg) 674 ENDIF 675 !!! RomP CALL histdef3d(iff,o_Vprecip%flag,o_Vprecip%name, "precipitation vertical profile", "-") 676 CALL histdef3d(iff,o_ftd) 677 CALL histdef3d(iff,o_fqd) 678 ENDIF !(iflag_con.EQ.3) 679 680 IF(iflag_con.GE.3) THEN ! RomP >>> 681 CALL histdef3d(iff,o_wdtrainA) 682 CALL histdef3d(iff,o_wdtrainM) 683 CALL histdef3d(iff,o_Vprecip) 684 ENDIF !(iflag_con.GE.3) ! <<< RomP 1613 685 1614 686 !!! nrlmd le 10/04/2012 1615 687 1616 IF (iflag_trig_bl>=1) THEN 1617 CALL histdef2d(iff,clef_stations(iff),o_n2%flag,o_n2%name, "Nombre de panaches de type 2", " ") 1618 CALL histdef2d(iff,clef_stations(iff),o_s2%flag,o_s2%name, "Surface moyenne des panaches de type 2", "m2") 1619 1620 CALL histdef2d(iff,clef_stations(iff),o_proba_notrig%flag,o_proba_notrig%name, "Probabilité de non-déclenchement", " ") 1621 CALL histdef2d(iff,clef_stations(iff),o_random_notrig%flag,o_random_notrig%name, "Tirage aléatoire de non-déclenchement", " ") 1622 CALL histdef2d(iff,clef_stations(iff),o_ale_bl_trig%flag,o_ale_bl_trig%name, "ALE_BL_STAT + Condition P>Pseuil", "m2/s2") 1623 CALL histdef2d(iff,clef_stations(iff),o_ale_bl_stat%flag,o_ale_bl_stat%name, "ALE_BL_STAT", "m2/s2") 1624 ENDIF !(iflag_trig_bl>=1) 1625 1626 IF (iflag_clos_bl>=1) THEN 1627 CALL histdef2d(iff,clef_stations(iff),o_alp_bl_det%flag,o_alp_bl_det%name, "ALP_BL_DET", "W/m2") 1628 CALL histdef2d(iff,clef_stations(iff),o_alp_bl_fluct_m%flag,o_alp_bl_fluct_m%name, "ALP_BL_FLUCT_M", "W/m2") 1629 CALL histdef2d(iff,clef_stations(iff),o_alp_bl_fluct_tke%flag,o_alp_bl_fluct_tke%name, "ALP_BL_FLUCT_TKE", "W/m2") 1630 CALL histdef2d(iff,clef_stations(iff),o_alp_bl_conv%flag,o_alp_bl_conv%name, "ALP_BL_CONV", "W/m2") 1631 CALL histdef2d(iff,clef_stations(iff),o_alp_bl_stat%flag,o_alp_bl_stat%name, "ALP_BL_STAT", "W/m2") 1632 ENDIF !(iflag_clos_bl>=1) 688 IF (iflag_trig_bl>=1) THEN 689 CALL histdef2d(iff,o_n2) 690 CALL histdef2d(iff,o_s2) 691 CALL histdef2d(iff,o_proba_notrig) 692 CALL histdef2d(iff,o_random_notrig) 693 CALL histdef2d(iff,o_ale_bl_trig) 694 CALL histdef2d(iff,o_ale_bl_stat) 695 ENDIF !(iflag_trig_bl>=1) 696 697 IF (iflag_clos_bl>=1) THEN 698 CALL histdef2d(iff,o_alp_bl_det) 699 CALL histdef2d(iff,o_alp_bl_fluct_m) 700 CALL histdef2d(iff,o_alp_bl_fluct_tke) 701 CALL histdef2d(iff,o_alp_bl_conv) 702 CALL histdef2d(iff,o_alp_bl_stat) 703 ENDIF !(iflag_clos_bl>=1) 1633 704 1634 705 !!! fin nrlmd le 10/04/2012 1635 1636 CALL histdef3d(iff,clef_stations(iff),o_dtlsc%flag,o_dtlsc%name, "Condensation dT", "K/s") 1637 CALL histdef3d(iff,clef_stations(iff),o_dtlschr%flag,o_dtlschr%name,"Large-scale condensational heating rate","K/s") 1638 CALL histdef3d(iff,clef_stations(iff),o_dqlsc%flag,o_dqlsc%name, "Condensation dQ", "(kg/kg)/s") 1639 CALL histdef3d(iff,clef_stations(iff),o_beta_prec%flag,o_beta_prec%name, "LS Conversion rate to prec", "(kg/kg)/s") 1640 CALL histdef3d(iff,clef_stations(iff),o_dtvdf%flag,o_dtvdf%name, "Boundary-layer dT", "K/s") 1641 CALL histdef3d(iff,clef_stations(iff),o_dtdis%flag,o_dtdis%name, "TKE dissipation dT", "K/s") 1642 CALL histdef3d(iff,clef_stations(iff),o_dqvdf%flag,o_dqvdf%name, "Boundary-layer dQ", "(kg/kg)/s") 1643 CALL histdef3d(iff,clef_stations(iff),o_dteva%flag,o_dteva%name, "Reevaporation dT", "K/s") 1644 CALL histdef3d(iff,clef_stations(iff),o_dqeva%flag,o_dqeva%name, "Reevaporation dQ", "(kg/kg)/s") 1645 CALL histdef3d(iff,clef_stations(iff),o_ptconv%flag,o_ptconv%name, "POINTS CONVECTIFS", " ") 1646 CALL histdef3d(iff,clef_stations(iff),o_ratqs%flag,o_ratqs%name, "RATQS", " ") 1647 CALL histdef3d(iff,clef_stations(iff),o_dtthe%flag,o_dtthe%name, "Thermal dT", "K/s") 1648 1649 if(iflag_thermals.ge.1) THEN 1650 CALL histdef3d(iff,clef_stations(iff),o_dqlscth%flag,o_dqlscth%name, "dQ therm.", "(kg/kg)/s") 1651 CALL histdef3d(iff,clef_stations(iff),o_dqlscst%flag,o_dqlscst%name, "dQ strat.", "(kg/kg)/s") 1652 CALL histdef3d(iff,clef_stations(iff),o_dtlscth%flag,o_dtlscth%name, "dQ therm.", "K/s") 1653 CALL histdef3d(iff,clef_stations(iff),o_dtlscst%flag,o_dtlscst%name, "dQ strat.", "K/s") 1654 CALL histdef2d(iff,clef_stations(iff),o_plulth%flag,o_plulth%name, "Rainfall therm.", "K/s") 1655 CALL histdef2d(iff,clef_stations(iff),o_plulst%flag,o_plulst%name, "Rainfall strat.", "K/s") 1656 CALL histdef2d(iff,clef_stations(iff),o_lmaxth%flag,o_lmaxth%name, "Upper level thermals", "") 1657 CALL histdef3d(iff,clef_stations(iff),o_ptconvth%flag,o_ptconvth%name, "POINTS CONVECTIFS therm.", " ") 1658 CALL histdef3d(iff,clef_stations(iff),o_f_th%flag,o_f_th%name, "Thermal plume mass flux", "kg/(m2*s)") 1659 CALL histdef3d(iff,clef_stations(iff),o_e_th%flag,o_e_th%name,"Thermal plume entrainment","K/s") 1660 CALL histdef3d(iff,clef_stations(iff),o_w_th%flag,o_w_th%name,"Thermal plume vertical velocity","m/s") 1661 CALL histdef3d(iff,clef_stations(iff), & 1662 o_lambda_th%flag,o_lambda_th%name,"Thermal plume vertical velocity","m/s") 1663 CALL histdef2d(iff,clef_stations(iff), & 1664 o_ftime_th%flag,o_ftime_th%name,"Fraction of time Shallow convection occurs"," ") 1665 CALL histdef3d(iff,clef_stations(iff), & 1666 o_q_th%flag,o_q_th%name, "Thermal plume total humidity", "kg/kg") 1667 CALL histdef3d(iff,clef_stations(iff), & 1668 o_a_th%flag,o_a_th%name, "Thermal plume fraction", "") 1669 CALL histdef3d(iff,clef_stations(iff), & 1670 o_d_th%flag,o_d_th%name, "Thermal plume detrainment", "K/s") 1671 1672 CALL histdef2d(iff,clef_stations(iff), & 1673 o_f0_th%flag,o_f0_th%name, "Thermal closure mass flux", "K/s") 1674 CALL histdef2d(iff,clef_stations(iff), & 1675 o_zmax_th%flag,o_zmax_th%name, "Thermal plume height", "K/s") 1676 CALL histdef3d(iff,clef_stations(iff), & 1677 o_dqthe%flag,o_dqthe%name, "Thermal dQ", "(kg/kg)/s") 1678 endif !iflag_thermals.ge.1 1679 CALL histdef3d(iff,clef_stations(iff), & 1680 o_dtajs%flag,o_dtajs%name, "Dry adjust. dT", "K/s") 1681 CALL histdef3d(iff,clef_stations(iff), & 1682 o_dqajs%flag,o_dqajs%name, "Dry adjust. dQ", "(kg/kg)/s") 1683 CALL histdef3d(iff,clef_stations(iff), & 1684 o_dtswr%flag,o_dtswr%name, "SW radiation dT", "K/s") 1685 CALL histdef3d(iff,clef_stations(iff), & 1686 o_dtsw0%flag,o_dtsw0%name, "CS SW radiation dT", "K/s") 1687 CALL histdef3d(iff,clef_stations(iff), & 1688 o_dtlwr%flag,o_dtlwr%name, "LW radiation dT", "K/s") 1689 CALL histdef3d(iff,clef_stations(iff), & 1690 o_dtlw0%flag,o_dtlw0%name, "CS LW radiation dT", "K/s") 1691 CALL histdef3d(iff,clef_stations(iff), & 1692 o_dtec%flag,o_dtec%name, "Cinetic dissip dT", "K/s") 1693 CALL histdef3d(iff,clef_stations(iff), & 1694 o_duvdf%flag,o_duvdf%name, "Boundary-layer dU", "m/s2") 1695 CALL histdef3d(iff,clef_stations(iff), & 1696 o_dvvdf%flag,o_dvvdf%name, "Boundary-layer dV", "m/s2") 1697 1698 IF (ok_orodr) THEN 1699 CALL histdef3d(iff,clef_stations(iff), & 1700 o_duoro%flag,o_duoro%name, "Orography dU", "m/s2") 1701 CALL histdef3d(iff,clef_stations(iff), & 1702 o_dvoro%flag,o_dvoro%name, "Orography dV", "m/s2") 1703 CALL histdef3d(iff,clef_stations(iff), & 1704 o_dtoro%flag,o_dtoro%name, "Orography dT", "K/s") 1705 ENDIF 1706 1707 IF (ok_orolf) THEN 1708 CALL histdef3d(iff,clef_stations(iff), & 1709 o_dulif%flag,o_dulif%name, "Orography dU", "m/s2") 1710 CALL histdef3d(iff,clef_stations(iff), & 1711 o_dvlif%flag,o_dvlif%name, "Orography dV", "m/s2") 1712 CALL histdef3d(iff,clef_stations(iff), & 1713 o_dtlif%flag,o_dtlif%name, "Orography dT", "K/s") 1714 ENDIF 1715 1716 IF (ok_hines) then 1717 CALL histdef3d(iff,clef_stations(iff), & 1718 o_duhin%flag,o_duhin%name, "Hines GWD dU", "m/s2") 1719 CALL histdef3d(iff,clef_stations(iff), & 1720 o_dvhin%flag,o_dvhin%name, "Hines GWD dV", "m/s2") 1721 1722 CALL histdef3d(iff,clef_stations(iff), & 1723 o_dthin%flag,o_dthin%name, "Hines GWD dT", "K/s") 1724 ENDIF 1725 1726 CALL histdef3d(iff,clef_stations(iff), & 1727 o_rsu%flag,o_rsu%name, "SW upward radiation", "W m-2") 1728 CALL histdef3d(iff,clef_stations(iff), & 1729 o_rsd%flag,o_rsd%name, "SW downward radiation", "W m-2") 1730 CALL histdef3d(iff,clef_stations(iff), & 1731 o_rlu%flag,o_rlu%name, "LW upward radiation", "W m-2") 1732 CALL histdef3d(iff,clef_stations(iff), & 1733 o_rld%flag,o_rld%name, "LW downward radiation", "W m-2") 1734 1735 CALL histdef3d(iff,clef_stations(iff), & 1736 o_rsucs%flag,o_rsucs%name, "SW CS upward radiation", "W m-2") 1737 CALL histdef3d(iff,clef_stations(iff), & 1738 o_rsdcs%flag,o_rsdcs%name, "SW CS downward radiation", "W m-2") 1739 CALL histdef3d(iff,clef_stations(iff), & 1740 o_rlucs%flag,o_rlucs%name, "LW CS upward radiation", "W m-2") 1741 CALL histdef3d(iff,clef_stations(iff), & 1742 o_rldcs%flag,o_rldcs%name, "LW CS downward radiation", "W m-2") 1743 1744 CALL histdef3d(iff,clef_stations(iff), & 1745 o_tnt%flag,o_tnt%name, "Tendency of air temperature", "K s-1") 1746 1747 CALL histdef3d(iff,clef_stations(iff), & 1748 o_tntc%flag,o_tntc%name, "Tendency of air temperature due to Moist Convection", & 1749 "K s-1") 1750 1751 CALL histdef3d(iff,clef_stations(iff), & 1752 o_tntr%flag,o_tntr%name, "Air temperature tendency due to Radiative heating", & 1753 "K s-1") 1754 1755 CALL histdef3d(iff,clef_stations(iff), & 1756 o_tntscpbl%flag,o_tntscpbl%name, "Air temperature tendency due to St cloud and precipitation and BL mixing", & 1757 "K s-1") 1758 1759 CALL histdef3d(iff,clef_stations(iff), & 1760 o_tnhus%flag,o_tnhus%name, "Tendency of specific humidity", "s-1") 1761 1762 CALL histdef3d(iff,clef_stations(iff), & 1763 o_tnhusc%flag,o_tnhusc%name, "Tendency of specific humidity due to convection", "s-1") 1764 1765 CALL histdef3d(iff,clef_stations(iff), & 1766 o_tnhusscpbl%flag,o_tnhusscpbl%name, "Tendency of Specific humidity due to ST cl, precip and BL mixing", & 1767 "s-1") 1768 1769 CALL histdef3d(iff,clef_stations(iff), & 1770 o_evu%flag,o_evu%name, "Eddy viscosity coefficient for Momentum Variables", "m2 s-1") 1771 1772 CALL histdef3d(iff,clef_stations(iff), & 1773 o_h2o%flag,o_h2o%name, "Mass Fraction of Water", "1") 1774 1775 CALL histdef3d(iff,clef_stations(iff), & 1776 o_mcd%flag,o_mcd%name, "Downdraft COnvective Mass Flux", "kg/(m2*s)") 1777 1778 CALL histdef3d(iff,clef_stations(iff), & 1779 o_dmc%flag,o_dmc%name, "Deep COnvective Mass Flux", "kg/(m2*s)") 1780 1781 CALL histdef3d(iff,clef_stations(iff), & 1782 o_ref_liq%flag,o_ref_liq%name, "Effective radius of convective cloud liquid water particle", "m") 1783 1784 CALL histdef3d(iff,clef_stations(iff), & 1785 o_ref_ice%flag,o_ref_ice%name, "Effective radius of startiform cloud ice particle", "m") 1786 1787 if (RCO2_per.NE.RCO2_act.OR.RCH4_per.NE.RCH4_act.OR. & 706 CALL histdef3d(iff,o_dtlsc) 707 CALL histdef3d(iff,o_dtlschr) 708 CALL histdef3d(iff,o_dqlsc) 709 CALL histdef3d(iff,o_beta_prec) 710 CALL histdef3d(iff,o_dtvdf) 711 CALL histdef3d(iff,o_dtdis) 712 CALL histdef3d(iff,o_dqvdf) 713 CALL histdef3d(iff,o_dteva) 714 CALL histdef3d(iff,o_dqeva) 715 CALL histdef3d(iff,o_ptconv) 716 CALL histdef3d(iff,o_ratqs) 717 CALL histdef3d(iff,o_dtthe) 718 719 IF (iflag_thermals.ge.1) THEN 720 CALL histdef3d(iff,o_dqlscth) 721 CALL histdef3d(iff,o_dqlscst) 722 CALL histdef3d(iff,o_dtlscth) 723 CALL histdef3d(iff,o_dtlscst) 724 CALL histdef2d(iff,o_plulth) 725 CALL histdef2d(iff,o_plulst) 726 CALL histdef2d(iff,o_lmaxth) 727 CALL histdef3d(iff,o_ptconvth) 728 CALL histdef3d(iff,o_f_th) 729 CALL histdef3d(iff,o_e_th) 730 CALL histdef3d(iff,o_w_th) 731 CALL histdef3d(iff,o_lambda_th) 732 CALL histdef2d(iff,o_ftime_th) 733 CALL histdef3d(iff,o_q_th) 734 CALL histdef3d(iff,o_a_th) 735 CALL histdef3d(iff,o_d_th) 736 CALL histdef2d(iff,o_f0_th) 737 CALL histdef2d(iff,o_zmax_th) 738 CALL histdef3d(iff,o_dqthe) 739 ENDIF !iflag_thermals.ge.1 740 741 CALL histdef3d(iff,o_dtajs) 742 CALL histdef3d(iff,o_dqajs) 743 CALL histdef3d(iff,o_dtswr) 744 CALL histdef3d(iff,o_dtsw0) 745 CALL histdef3d(iff,o_dtlwr) 746 CALL histdef3d(iff,o_dtlw0) 747 CALL histdef3d(iff,o_dtec) 748 CALL histdef3d(iff,o_duvdf) 749 CALL histdef3d(iff,o_dvvdf) 750 751 IF (ok_orodr) THEN 752 CALL histdef3d(iff,o_duoro) 753 CALL histdef3d(iff,o_dvoro) 754 CALL histdef3d(iff,o_dtoro) 755 ENDIF 756 757 IF (ok_orolf) THEN 758 CALL histdef3d(iff,o_dulif) 759 CALL histdef3d(iff,o_dvlif) 760 CALL histdef3d(iff,o_dtlif) 761 ENDIF 762 763 IF (ok_hines) then 764 CALL histdef3d(iff,o_duhin) 765 CALL histdef3d(iff,o_dvhin) 766 CALL histdef3d(iff,o_dthin) 767 ENDIF 768 769 CALL histdef3d(iff,o_rsu) 770 CALL histdef3d(iff,o_rsd) 771 CALL histdef3d(iff,o_rlu) 772 CALL histdef3d(iff,o_rld) 773 CALL histdef3d(iff,o_rsucs) 774 CALL histdef3d(iff,o_rsdcs) 775 CALL histdef3d(iff,o_rlucs) 776 CALL histdef3d(iff,o_rldcs) 777 CALL histdef3d(iff,o_tnt) 778 CALL histdef3d(iff,o_tntc) 779 CALL histdef3d(iff,o_tntr) 780 CALL histdef3d(iff,o_tntscpbl) 781 CALL histdef3d(iff,o_tnhus) 782 CALL histdef3d(iff,o_tnhusc) 783 CALL histdef3d(iff,o_tnhusscpbl) 784 CALL histdef3d(iff,o_evu) 785 CALL histdef3d(iff,o_h2o) 786 CALL histdef3d(iff,o_mcd) 787 CALL histdef3d(iff,o_dmc) 788 CALL histdef3d(iff,o_ref_liq) 789 CALL histdef3d(iff,o_ref_ice) 790 791 IF (RCO2_per.NE.RCO2_act.OR.RCH4_per.NE.RCH4_act.OR. & 1788 792 RN2O_per.NE.RN2O_act.OR.RCFC11_per.NE.RCFC11_act.OR. & 1789 793 RCFC12_per.NE.RCFC12_act) THEN 1790 1791 CALL histdef2d(iff,clef_stations(iff),o_rsut4co2%flag,o_rsut4co2%name, & 1792 "TOA Out SW in 4xCO2 atmosphere", "W/m2") 1793 CALL histdef2d(iff,clef_stations(iff),o_rlut4co2%flag,o_rlut4co2%name, & 1794 "TOA Out LW in 4xCO2 atmosphere", "W/m2") 1795 CALL histdef2d(iff,clef_stations(iff),o_rsutcs4co2%flag,o_rsutcs4co2%name, & 1796 "TOA Out CS SW in 4xCO2 atmosphere", "W/m2") 1797 CALL histdef2d(iff,clef_stations(iff),o_rlutcs4co2%flag,o_rlutcs4co2%name, & 1798 "TOA Out CS LW in 4xCO2 atmosphere", "W/m2") 1799 1800 CALL histdef3d(iff,clef_stations(iff),o_rsu4co2%flag,o_rsu4co2%name, & 1801 "Upwelling SW 4xCO2 atmosphere", "W/m2") 1802 CALL histdef3d(iff,clef_stations(iff),o_rlu4co2%flag,o_rlu4co2%name, & 1803 "Upwelling LW 4xCO2 atmosphere", "W/m2") 1804 CALL histdef3d(iff,clef_stations(iff),o_rsucs4co2%flag,o_rsucs4co2%name, & 1805 "Upwelling CS SW 4xCO2 atmosphere", "W/m2") 1806 CALL histdef3d(iff,clef_stations(iff),o_rlucs4co2%flag,o_rlucs4co2%name, & 1807 "Upwelling CS LW 4xCO2 atmosphere", "W/m2") 1808 1809 CALL histdef3d(iff,clef_stations(iff),o_rsd4co2%flag,o_rsd4co2%name, & 1810 "Downwelling SW 4xCO2 atmosphere", "W/m2") 1811 CALL histdef3d(iff,clef_stations(iff),o_rld4co2%flag,o_rld4co2%name, & 1812 "Downwelling LW 4xCO2 atmosphere", "W/m2") 1813 CALL histdef3d(iff,clef_stations(iff),o_rsdcs4co2%flag,o_rsdcs4co2%name, & 1814 "Downwelling CS SW 4xCO2 atmosphere", "W/m2") 1815 CALL histdef3d(iff,clef_stations(iff),o_rldcs4co2%flag,o_rldcs4co2%name, & 1816 "Downwelling CS LW 4xCO2 atmosphere", "W/m2") 1817 1818 endif 1819 1820 1821 IF (nqtot>=3) THEN 1822 DO iq=3,nqtot 1823 iiq=niadv(iq) 1824 o_trac(iq-2) = ctrl_out((/ 4, 5, 1, 1, 1, 10 /),tname(iiq)) 1825 CALL histdef3d (iff,clef_stations(iff), & 1826 o_trac(iq-2)%flag,o_trac(iq-2)%name,'Tracer '//ttext(iiq), "-" ) 1827 o_trac_cum(iq-2) = ctrl_out((/ 3, 4, 10, 10, 10, 10 /),'cum'//tname(iiq)) 1828 CALL histdef2d (iff,clef_stations(iff), & 1829 o_trac_cum(iq-2)%flag,o_trac_cum(iq-2)%name,'Cumulated tracer '//ttext(iiq), "-" ) 1830 ENDDO 1831 ENDIF 1832 1833 CALL histend(nid_files(iff)) 1834 1835 ndex2d = 0 1836 ndex3d = 0 1837 1838 ENDIF ! clef_files 794 CALL histdef2d(iff,o_rsut4co2) 795 CALL histdef2d(iff,o_rlut4co2) 796 CALL histdef2d(iff,o_rsutcs4co2) 797 CALL histdef2d(iff,o_rlutcs4co2) 798 CALL histdef3d(iff,o_rsu4co2) 799 CALL histdef3d(iff,o_rlu4co2) 800 CALL histdef3d(iff,o_rsucs4co2) 801 CALL histdef3d(iff,o_rlucs4co2) 802 CALL histdef3d(iff,o_rsd4co2) 803 CALL histdef3d(iff,o_rld4co2) 804 CALL histdef3d(iff,o_rsdcs4co2) 805 CALL histdef3d(iff,o_rldcs4co2) 806 807 ENDIF 808 809 810 IF (nqtot>=3) THEN 811 DO iq=3,nqtot 812 iiq=niadv(iq) 813 o_trac(iq-2) = ctrl_out((/ 4, 5, 1, 1, 1, 10 /),tname(iiq),'Tracer '//ttext(iiq), "-",& 814 (/ '', '', '', '', '', '' /)) 815 CALL histdef3d(iff, o_trac(iq-2)) 816 o_trac_cum(iq-2) = ctrl_out((/ 3, 4, 10, 10, 10, 10 /),'cum'//tname(iiq),& 817 'Cumulated tracer '//ttext(iiq), "-", (/ '', '', '', '', '', '' /)) 818 CALL histdef2d(iff, o_trac_cum(iq-2)) 819 ENDDO 820 ENDIF 821 822 CALL histend(nid_files(iff)) 823 824 ndex2d = 0 825 ndex3d = 0 826 827 ENDIF ! clef_files 1839 828 1840 829 ENDDO ! iff … … 1849 838 ecrit_ins = ecrit_files(6) 1850 839 1851 write(lunout,*)'swaero_diag=',swaero_diag1852 write(lunout,*)'Fin phys_output_mod.F90'1853 end subroutinephys_output_open1854 1855 SUBROUTINE histdef2d (iff,lpoint,flag_var,nomvar,titrevar,unitvar)1856 1857 useioipsl840 WRITE(lunout,*)'swaero_diag=',swaero_diag 841 WRITE(lunout,*)'Fin phys_output_mod.F90' 842 end SUBROUTINE phys_output_open 843 844 SUBROUTINE histdef2d_old (iff,lpoint,flag_var,nomvar,titrevar,unitvar) 845 846 USE ioipsl 1858 847 USE dimphy 1859 848 USE mod_phys_lmdz_para … … 1862 851 IMPLICIT NONE 1863 852 1864 include"dimensions.h"1865 include"temps.h"1866 include"clesphys.h"1867 1868 integer:: iff1869 logical:: lpoint1870 integer, dimension(nfiles) :: flag_var1871 character(len=20) :: nomvar1872 character(len=*) :: titrevar1873 character(len=*) :: unitvar1874 1875 realzstophym1876 1877 if (type_ecri(iff)=='inst(X)'.OR.type_ecri(iff)=='once') then853 INCLUDE "dimensions.h" 854 INCLUDE "temps.h" 855 INCLUDE "clesphys.h" 856 857 INTEGER :: iff 858 LOGICAL :: lpoint 859 INTEGER, DIMENSION(nfiles) :: flag_var 860 CHARACTER(LEN=20) :: nomvar 861 CHARACTER(LEN=*) :: titrevar 862 CHARACTER(LEN=*) :: unitvar 863 864 REAL zstophym 865 866 IF (type_ecri(iff)=='inst(X)'.OR.type_ecri(iff)=='once') THEN 1878 867 zstophym=zoutm(iff) 1879 else868 ELSE 1880 869 zstophym=zdtime 1881 endif870 ENDIF 1882 871 1883 872 ! Appel a la lecture des noms et niveau d'ecriture des variables dans output.def 1884 callconf_physoutputs(nomvar,flag_var)1885 1886 if(.NOT.lpoint) THEN1887 if ( flag_var(iff)<=lev_files(iff) ) then1888 callhistdef (nid_files(iff),nomvar,titrevar,unitvar, &873 CALL conf_physoutputs(nomvar,flag_var) 874 875 IF(.NOT.lpoint) THEN 876 IF ( flag_var(iff)<=lev_files(iff) ) THEN 877 CALL histdef (nid_files(iff),nomvar,titrevar,unitvar, & 1889 878 iim,jj_nb,nhorim(iff), 1,1,1, -99, 32, & 1890 879 type_ecri(iff), zstophym,zoutm(iff)) 1891 endif1892 else1893 if ( flag_var(iff)<=lev_files(iff) ) then1894 callhistdef (nid_files(iff),nomvar,titrevar,unitvar, &880 ENDIF 881 ELSE 882 IF ( flag_var(iff)<=lev_files(iff) ) THEN 883 CALL histdef (nid_files(iff),nomvar,titrevar,unitvar, & 1895 884 npstn,1,nhorim(iff), 1,1,1, -99, 32, & 1896 885 type_ecri(iff), zstophym,zoutm(iff)) 1897 endif1898 endif886 ENDIF 887 ENDIF 1899 888 1900 889 ! Set swaero_diag=true if at least one of the concerned variables are defined 1901 if(nomvar=='topswad' .OR. nomvar=='topswai' .OR. nomvar=='solswad' .OR. nomvar=='solswai' ) THEN1902 if ( flag_var(iff)<=lev_files(iff) ) then890 IF (nomvar=='topswad' .OR. nomvar=='topswai' .OR. nomvar=='solswad' .OR. nomvar=='solswai' ) THEN 891 IF ( flag_var(iff)<=lev_files(iff) ) THEN 1903 892 swaero_diag=.TRUE. 1904 end if1905 end if1906 end subroutine histdef2d1907 1908 SUBROUTINE histdef 3d (iff,lpoint,flag_var,nomvar,titrevar,unitvar)1909 1910 useioipsl893 END IF 894 END IF 895 END SUBROUTINE histdef2d_old 896 897 SUBROUTINE histdef2d (iff,var) 898 899 USE ioipsl 1911 900 USE dimphy 1912 901 USE mod_phys_lmdz_para … … 1915 904 IMPLICIT NONE 1916 905 1917 include "dimensions.h" 1918 include "temps.h" 1919 include "clesphys.h" 1920 1921 integer :: iff 1922 logical :: lpoint 1923 integer, dimension(nfiles) :: flag_var 1924 character(len=20) :: nomvar 1925 character(len=*) :: titrevar 1926 character(len=*) :: unitvar 1927 1928 real zstophym 906 INCLUDE "dimensions.h" 907 INCLUDE "temps.h" 908 INCLUDE "clesphys.h" 909 910 INTEGER :: iff 911 TYPE(ctrl_out) :: var 912 913 REAL zstophym 914 CHARACTER(LEN=20) :: typeecrit 915 916 ! ug On récupère le type écrit de la structure: 917 ! Assez moche, à refaire si meilleure méthode... 918 IF (INDEX(var%type_ecrit(iff), "once") > 0) THEN 919 typeecrit = 'once' 920 ELSE IF(INDEX(var%type_ecrit(iff), "t_min") > 0) THEN 921 typeecrit = 't_min(X)' 922 ELSE IF(INDEX(var%type_ecrit(iff), "t_max") > 0) THEN 923 typeecrit = 't_max(X)' 924 ELSE IF(INDEX(var%type_ecrit(iff), "inst") > 0) THEN 925 typeecrit = 'inst(X)' 926 ELSE 927 typeecrit = type_ecri_files(iff) 928 ENDIF 929 930 IF (typeecrit=='inst(X)'.OR.typeecrit=='once') THEN 931 zstophym=zoutm(iff) 932 ELSE 933 zstophym=zdtime 934 ENDIF 1929 935 1930 936 ! Appel a la lecture des noms et niveau d'ecriture des variables dans output.def 1931 call conf_physoutputs(nomvar,flag_var) 1932 1933 if (type_ecri(iff)=='inst(X)'.OR.type_ecri(iff)=='once') then 937 CALL conf_physoutputs(var%name, var%flag) 938 939 IF(.NOT.clef_stations(iff)) THEN 940 IF ( var%flag(iff)<=lev_files(iff) ) THEN 941 CALL histdef (nid_files(iff), var%name, var%description, var%unit, & 942 iim,jj_nb,nhorim(iff), 1,1,1, -99, 32, & 943 typeecrit, zstophym,zoutm(iff)) 944 ENDIF 945 ELSE 946 IF ( var%flag(iff)<=lev_files(iff)) THEN 947 CALL histdef (nid_files(iff), var%name, var%description, var%unit, & 948 npstn,1,nhorim(iff), 1,1,1, -99, 32, & 949 typeecrit, zstophym,zoutm(iff)) 950 ENDIF 951 ENDIF 952 953 ! Set swaero_diag=true if at least one of the concerned variables are defined 954 IF (var%name=='topswad' .OR. var%name=='topswai' .OR. var%name=='solswad' .OR. var%name=='solswai' ) THEN 955 IF ( var%flag(iff)<=lev_files(iff) ) THEN 956 swaero_diag=.TRUE. 957 END IF 958 END IF 959 END SUBROUTINE histdef2d 960 961 SUBROUTINE histdef3d_old (iff,lpoint,flag_var,nomvar,titrevar,unitvar) 962 963 USE ioipsl 964 USE dimphy 965 USE mod_phys_lmdz_para 966 USE iophy 967 968 IMPLICIT NONE 969 970 INCLUDE "dimensions.h" 971 INCLUDE "temps.h" 972 ! INCLUDE "indicesol.h" 973 INCLUDE "clesphys.h" 974 975 INTEGER :: iff 976 LOGICAL :: lpoint 977 INTEGER, DIMENSION(nfiles) :: flag_var 978 CHARACTER(LEN=20) :: nomvar 979 CHARACTER(LEN=*) :: titrevar 980 CHARACTER(LEN=*) :: unitvar 981 982 REAL zstophym 983 984 ! Appel a la lecture des noms et niveau d'ecriture des variables dans output.def 985 CALL conf_physoutputs(nomvar,flag_var) 986 987 IF (type_ecri(iff)=='inst(X)'.OR.type_ecri(iff)=='once') THEN 1934 988 zstophym=zoutm(iff) 1935 else989 ELSE 1936 990 zstophym=zdtime 1937 endif1938 1939 if(.NOT.lpoint) THEN1940 if ( flag_var(iff)<=lev_files(iff) ) then1941 callhistdef (nid_files(iff), nomvar, titrevar, unitvar, &991 ENDIF 992 993 IF(.NOT.lpoint) THEN 994 IF ( flag_var(iff)<=lev_files(iff) ) THEN 995 CALL histdef (nid_files(iff), nomvar, titrevar, unitvar, & 1942 996 iim, jj_nb, nhorim(iff), klev, levmin(iff), & 1943 997 levmax(iff)-levmin(iff)+1, nvertm(iff), 32, type_ecri(iff), & 1944 998 zstophym, zoutm(iff)) 1945 endif1946 else1947 if ( flag_var(iff)<=lev_files(iff) ) then1948 callhistdef (nid_files(iff), nomvar, titrevar, unitvar, &999 ENDIF 1000 ELSE 1001 IF ( flag_var(iff)<=lev_files(iff) ) THEN 1002 CALL histdef (nid_files(iff), nomvar, titrevar, unitvar, & 1949 1003 npstn,1,nhorim(iff), klev, levmin(iff), & 1950 1004 levmax(iff)-levmin(iff)+1, nvertm(iff), 32, & 1951 1005 type_ecri(iff), zstophym,zoutm(iff)) 1952 endif 1953 endif 1954 end subroutine histdef3d 1006 ENDIF 1007 ENDIF 1008 END SUBROUTINE histdef3d_old 1009 1010 SUBROUTINE histdef3d (iff,var) 1011 1012 USE ioipsl 1013 USE dimphy 1014 USE mod_phys_lmdz_para 1015 USE iophy 1016 1017 IMPLICIT NONE 1018 1019 INCLUDE "dimensions.h" 1020 INCLUDE "temps.h" 1021 INCLUDE "clesphys.h" 1022 1023 INTEGER :: iff 1024 TYPE(ctrl_out) :: var 1025 1026 REAL zstophym 1027 CHARACTER(LEN=20) :: typeecrit 1028 1029 ! ug On récupère le type écrit de la structure: 1030 ! Assez moche, à refaire si meilleure méthode... 1031 IF (INDEX(var%type_ecrit(iff), "once") > 0) THEN 1032 typeecrit = 'once' 1033 ELSE IF(INDEX(var%type_ecrit(iff), "t_min") > 0) THEN 1034 typeecrit = 't_min(X)' 1035 ELSE IF(INDEX(var%type_ecrit(iff), "t_max") > 0) THEN 1036 typeecrit = 't_max(X)' 1037 ELSE IF(INDEX(var%type_ecrit(iff), "inst") > 0) THEN 1038 typeecrit = 'inst(X)' 1039 ELSE 1040 typeecrit = type_ecri_files(iff) 1041 ENDIF 1042 1043 1044 ! Appel a la lecture des noms et niveau d'ecriture des variables dans output.def 1045 CALL conf_physoutputs(var%name,var%flag) 1046 1047 IF (typeecrit=='inst(X)'.OR.typeecrit=='once') THEN 1048 zstophym=zoutm(iff) 1049 ELSE 1050 zstophym=zdtime 1051 ENDIF 1052 1053 IF(.NOT.clef_stations(iff)) THEN 1054 IF ( var%flag(iff)<=lev_files(iff) ) THEN 1055 CALL histdef (nid_files(iff), var%name, var%description, var%unit, & 1056 iim, jj_nb, nhorim(iff), klev, levmin(iff), & 1057 levmax(iff)-levmin(iff)+1, nvertm(iff), 32, typeecrit, & 1058 zstophym, zoutm(iff)) 1059 ENDIF 1060 ELSE 1061 IF ( var%flag(iff)<=lev_files(iff)) THEN 1062 CALL histdef (nid_files(iff), var%name, var%description, var%unit, & 1063 npstn,1,nhorim(iff), klev, levmin(iff), & 1064 levmax(iff)-levmin(iff)+1, nvertm(iff), 32, & 1065 typeecrit, zstophym,zoutm(iff)) 1066 ENDIF 1067 ENDIF 1068 END SUBROUTINE histdef3d 1955 1069 1956 1070 SUBROUTINE conf_physoutputs(nam_var,flag_var) … … 1963 1077 include 'iniprint.h' 1964 1078 1965 character(len=20) :: nam_var1966 integer, dimension(nfiles) :: flag_var1079 CHARACTER(LEN=20) :: nam_var 1080 INTEGER, DIMENSION(nfiles) :: flag_var 1967 1081 1968 1082 IF(prt_level>10) WRITE(lunout,*)'Avant getin: nam_var flag_var ',nam_var,flag_var(:) 1969 callgetin('flag_'//nam_var,flag_var)1970 callgetin('name_'//nam_var,nam_var)1083 CALL getin('flag_'//nam_var,flag_var) 1084 CALL getin('name_'//nam_var,nam_var) 1971 1085 IF(prt_level>10) WRITE(lunout,*)'Apres getin: nam_var flag_var ',nam_var,flag_var(:) 1972 1086 … … 1980 1094 IMPLICIT NONE 1981 1095 1982 character(len=20) :: str1983 character(len=10) :: type1984 integer:: ipos,il1096 CHARACTER(LEN=20) :: str 1097 CHARACTER(LEN=10) :: type 1098 INTEGER :: ipos,il 1985 1099 real :: ttt,xxx,timestep,dayseconde,dtime 1986 1100 parameter (dayseconde=86400.) … … 1989 1103 include "iniprint.h" 1990 1104 1991 ipos=scan(str,'0123456789.',. true.)1105 ipos=scan(str,'0123456789.',.TRUE.) 1992 1106 ! 1993 1107 il=len_trim(str) 1994 write(lunout,*)ipos,il1108 WRITE(lunout,*)ipos,il 1995 1109 read(str(1:ipos),*) ttt 1996 write(lunout,*)ttt1110 WRITE(lunout,*)ttt 1997 1111 type=str(ipos+1:il) 1998 1112 1999 1113 2000 if( il == ipos ) then1114 IF ( il == ipos ) then 2001 1115 type='day' 2002 1116 endif 2003 1117 2004 if( type == 'day'.or.type == 'days'.or.type == 'jours'.or.type == 'jour' ) timestep = ttt * dayseconde2005 if( type == 'mounths'.or.type == 'mth'.or.type == 'mois' ) then2006 write(lunout,*)'annee_ref,day_ref mon_len',annee_ref,day_ref,mth_len1118 IF ( type == 'day'.or.type == 'days'.or.type == 'jours'.or.type == 'jour' ) timestep = ttt * dayseconde 1119 IF ( type == 'mounths'.or.type == 'mth'.or.type == 'mois' ) then 1120 WRITE(lunout,*)'annee_ref,day_ref mon_len',annee_ref,day_ref,mth_len 2007 1121 timestep = ttt * dayseconde * mth_len 2008 1122 endif 2009 if( type == 'hours'.or.type == 'hr'.or.type == 'heurs') timestep = ttt * dayseconde / 24.2010 if( type == 'mn'.or.type == 'minutes' ) timestep = ttt * 60.2011 if( type == 's'.or.type == 'sec'.or.type == 'secondes' ) timestep = ttt2012 if( type == 'TS' ) timestep = ttt * dtime2013 2014 write(lunout,*)'type = ',type2015 write(lunout,*)'nb j/h/m = ',ttt2016 write(lunout,*)'timestep(s)=',timestep1123 IF ( type == 'hours'.or.type == 'hr'.or.type == 'heurs') timestep = ttt * dayseconde / 24. 1124 IF ( type == 'mn'.or.type == 'minutes' ) timestep = ttt * 60. 1125 IF ( type == 's'.or.type == 'sec'.or.type == 'secondes' ) timestep = ttt 1126 IF ( type == 'TS' ) timestep = ttt * dtime 1127 1128 WRITE(lunout,*)'type = ',type 1129 WRITE(lunout,*)'nb j/h/m = ',ttt 1130 WRITE(lunout,*)'timestep(s)=',timestep 2017 1131 2018 1132 END SUBROUTINE convers_timesteps -
LMDZ5/trunk/libf/phylmd/phys_output_var_mod.F90
r1761 r1791 14 14 REAL, SAVE, ALLOCATABLE :: snow_o(:), zfra_o(:) 15 15 !$OMP THREADPRIVATE(snow_o, zfra_o) 16 INTEGER, save, ALLOCATABLE :: itau_con(:) ! Nombre de pas ou rflag <= 116 INTEGER, SAVE, ALLOCATABLE :: itau_con(:) ! Nombre de pas ou rflag <= 1 17 17 !$OMP THREADPRIVATE(itau_con) 18 18 REAL, ALLOCATABLE :: bils_ec(:) ! Contribution of energy conservation … … 24 24 !$OMP THREADPRIVATE(bils_ec,bils_tke,bils_diss,bils_kinetic,bils_enthalp,bils_latent) 25 25 26 ! ug Plein de variables venues de phys_output_mod 27 INTEGER, PARAMETER :: nfiles = 6 28 LOGICAL, DIMENSION(nfiles), SAVE :: clef_files 29 LOGICAL, DIMENSION(nfiles), SAVE :: clef_stations 30 INTEGER, DIMENSION(nfiles), SAVE :: lev_files 31 INTEGER, DIMENSION(nfiles), SAVE :: nid_files 32 INTEGER, DIMENSION(nfiles), SAVE :: nnid_files 33 !$OMP THREADPRIVATE(clef_files, clef_stations, lev_files,nid_files,nnid_files) 34 INTEGER, DIMENSION(nfiles), SAVE :: nnhorim 26 35 36 INTEGER, DIMENSION(nfiles), SAVE :: nhorim, nvertm 37 INTEGER, DIMENSION(nfiles), SAVE :: nvertap, nvertbp, nvertAlt 38 REAL, DIMENSION(nfiles), SAVE :: zoutm 39 CHARACTER(LEN=20), DIMENSION(nfiles), SAVE :: type_ecri 40 !$OMP THREADPRIVATE(nnhorim, nhorim, nvertm, zoutm,type_ecri) 41 CHARACTER(LEN=20), DIMENSION(nfiles), SAVE :: type_ecri_files, phys_out_filetypes 42 !$OMP THREADPRIVATE(type_ecri_files, phys_out_filetypes) 43 44 ! swaero_diag : flag indicates if it is necessary to do calculation for some aerosol diagnostics 45 LOGICAL, SAVE :: swaero_diag=.FALSE. 46 !$OMP THREADPRIVATE(swaero_diag) 47 48 INTEGER, SAVE:: levmin(nfiles) = 1 49 INTEGER, SAVE:: levmax(nfiles) 50 !$OMP THREADPRIVATE(levmin, levmax) 51 52 TYPE ctrl_out 53 INTEGER,DIMENSION(nfiles) :: flag 54 CHARACTER(len=20) :: name 55 CHARACTER(len=150) :: description 56 CHARACTER(len=20) :: unit 57 CHARACTER(len=20),DIMENSION(nfiles) :: type_ecrit 58 END TYPE ctrl_out 27 59 CONTAINS 28 60 -
LMDZ5/trunk/libf/phylmd/phys_output_write.h
r1764 r1791 795 795 ll=ll+1 796 796 IF (o_uSTDlevs(ll)%flag(iff)<=lev_files(iff)) THEN 797 CALL histwrite_phy(nid_files(iff),clef_stations(iff),798 $o_uSTDlevs(ll)%name,799 & itau_w,uwriteSTD(:,k,iff))797 ! CALL histwrite_phy(nid_files(iff),clef_stations(iff), 798 ! $o_uSTDlevs(ll)%name, 799 ! & itau_w,uwriteSTD(:,k,iff)) 800 800 ENDIF 801 801 802 802 IF (o_vSTDlevs(ll)%flag(iff)<=lev_files(iff)) THEN 803 CALL histwrite_phy(nid_files(iff),clef_stations(iff),804 $o_vSTDlevs(ll)%name,805 & itau_w,vwriteSTD(:,k,iff))803 ! CALL histwrite_phy(nid_files(iff),clef_stations(iff), 804 ! $o_vSTDlevs(ll)%name, 805 ! & itau_w,vwriteSTD(:,k,iff)) 806 806 ENDIF 807 807 808 808 IF (o_wSTDlevs(ll)%flag(iff)<=lev_files(iff)) THEN 809 CALL histwrite_phy(nid_files(iff),clef_stations(iff),810 $o_wSTDlevs(ll)%name,811 & itau_w,wwriteSTD(:,k,iff))809 ! CALL histwrite_phy(nid_files(iff),clef_stations(iff), 810 ! $o_wSTDlevs(ll)%name, 811 ! & itau_w,wwriteSTD(:,k,iff)) 812 812 ENDIF 813 813 814 814 IF (o_zSTDlevs(ll)%flag(iff)<=lev_files(iff)) THEN 815 CALL histwrite_phy(nid_files(iff),clef_stations(iff),816 $o_zSTDlevs(ll)%name,817 & itau_w,phiwriteSTD(:,k,iff))815 ! CALL histwrite_phy(nid_files(iff),clef_stations(iff), 816 ! $o_zSTDlevs(ll)%name, 817 ! & itau_w,phiwriteSTD(:,k,iff)) 818 818 ENDIF 819 819 820 820 IF (o_qSTDlevs(ll)%flag(iff)<=lev_files(iff)) THEN 821 CALL histwrite_phy(nid_files(iff),clef_stations(iff),822 $o_qSTDlevs(ll)%name,823 & itau_w, qwriteSTD(:,k,iff))821 ! CALL histwrite_phy(nid_files(iff),clef_stations(iff), 822 ! $o_qSTDlevs(ll)%name, 823 ! & itau_w, qwriteSTD(:,k,iff)) 824 824 ENDIF 825 825 826 826 IF (o_tSTDlevs(ll)%flag(iff)<=lev_files(iff)) THEN 827 CALL histwrite_phy(nid_files(iff),clef_stations(iff),828 $o_tSTDlevs(ll)%name,829 & itau_w, twriteSTD(:,k,iff))827 ! CALL histwrite_phy(nid_files(iff),clef_stations(iff), 828 ! $o_tSTDlevs(ll)%name, 829 ! & itau_w, twriteSTD(:,k,iff)) 830 830 ENDIF 831 831 -
LMDZ5/trunk/libf/phylmd/physiq.F
r1785 r1791 31 31 USE fonte_neige_mod, ONLY : fonte_neige_get_vars 32 32 USE phys_output_mod 33 USE phys_output_ctrlout_mod 34 USE iophy 33 35 use open_climoz_m, only: open_climoz ! ozone climatology from a file 34 36 use regr_pr_av_m, only: regr_pr_av … … 4029 4031 endif 4030 4032 4031 #include "phys_output_write.h" 4033 #include "phys_output_write_new.h" 4034 4035 4036 4032 4037 4033 4038 #ifdef histISCCP
Note: See TracChangeset
for help on using the changeset viewer.