Ignore:
Timestamp:
May 29, 2018, 3:16:06 PM (6 years ago)
Author:
Laurent Fairhead
Message:

Continuing merge of DYNAMICO and LMDZ physics. With this revision all differences with the
LMDZ physics branch of DYNAMICO have been integrated in LMDZ6 branch. Now for the merge
with trunk

Location:
LMDZ6/branches/DYNAMICO-conv/libf
Files:
6 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/DYNAMICO-conv/libf/misc/wxios.F90

    r3322 r3336  
    1515   
    1616    INTEGER, SAVE :: g_comm
    17     CHARACTER(len=100), SAVE :: g_ctx_name
     17    CHARACTER(len=100), SAVE :: g_ctx_name ="LMDZ"
    1818    TYPE(xios_context), SAVE :: g_ctx
    1919!$OMP THREADPRIVATE(g_comm,g_cts_name,g_ctx)
     
    145145    SUBROUTINE wxios_context_init()
    146146        USE print_control_mod, ONLY : prt_level, lunout
    147 !        USE mod_phys_lmdz_mpi_data, ONLY : COMM_LMDZ_PHY
     147        USE mod_phys_lmdz_mpi_data, ONLY : COMM_LMDZ_PHY
    148148        IMPLICIT NONE
    149149
     
    152152!$OMP MASTER
    153153        !Initialisation du contexte:
    154         CALL xios_context_initialize(g_ctx_name, g_comm)
     154        CALL xios_context_initialize(g_ctx_name, COMM_LMDZ_PHY)
    155155        CALL xios_get_handle(g_ctx_name, xios_ctx)    !Récupération
    156156        CALL xios_set_current_context(xios_ctx)            !Activation
  • LMDZ6/branches/DYNAMICO-conv/libf/phylmd/limit_read_mod.F90

    r3312 r3336  
    288288
    289289    is_modified = .FALSE.
    290     IF (MOD(itime-1, lmt_pas) == 0 .OR. jour_lu /= jour ) THEN   ! time to read
     290!ym    IF (MOD(itime-1, lmt_pas) == 0 .OR. jour_lu /= jour ) THEN   ! time to read
     291!  not REALLY PERIODIC
     292    IF (MOD(itime-1, lmt_pas) == 0) THEN   ! time to read
    291293       jour_lu = jour
    292294       is_modified = .TRUE.
  • LMDZ6/branches/DYNAMICO-conv/libf/phylmd/phys_cal_mod.F90

    r2802 r3336  
    3636 
    3737  SUBROUTINE phys_cal_init(annee_ref,day_ref)
    38 
    39     USE IOIPSL, ONLY:  ymds2ju
    40     USE ioipsl_getin_p_mod, ONLY: getin_p
    41 
    42     IMPLICIT NONE
     38  USE IOIPSL, ONLY:  ymds2ju, ioconf_calendar
     39  USE mod_phys_lmdz_para, ONLY:  is_master,is_omp_master
     40  USE ioipsl_getin_p_mod, ONLY: getin_p
     41  IMPLICIT NONE
    4342    INTEGER,INTENT(IN) :: annee_ref
    4443    INTEGER,INTENT(IN) :: day_ref
     
    4847    CALL getin_p("calend",calend)
    4948     
     49    IF (is_omp_master) THEN
     50      IF (calend == 'earth_360d') THEN
     51        CALL ioconf_calendar('360d')
     52      ELSE IF (calend == 'earth_365d') THEN
     53        CALL ioconf_calendar('noleap')
     54      ELSE IF (calend == 'earth_366d') THEN
     55        CALL ioconf_calendar('gregorian')
     56      ELSE
     57        CALL abort_physic('phys_cal_init','Mauvais choix de calendrier',1)
     58      ENDIF
     59    ENDIF
     60!$OMP BARRIER
     61
    5062    CALL ymds2ju(annee_ref, 1, day_ref, 0., jD_ref)
    5163    jD_ref=INT(jD_ref)
  • LMDZ6/branches/DYNAMICO-conv/libf/phylmd/phys_output_write_mod.F90

    r3003 r3336  
    348348    ! ug Pour les sorties XIOS
    349349    USE xios
    350     USE wxios, ONLY: wxios_closedef, missing_val
     350    USE wxios, ONLY: wxios_closedef, missing_val, wxios_set_context
    351351#endif
    352352    USE phys_cal_mod, ONLY : mth_len
     
    417417    CALL set_itau_iophy(itau_w)
    418418
    419     IF (.NOT.vars_defined) THEN
    420        iinitend = 2
    421     ELSE
     419 !   IF (.NOT.vars_defined) THEN
    422420       iinitend = 1
    423     ENDIF
     421 !   ELSE
     422 !      iinitend = 1
     423 !   ENDIF
     424
     425#ifdef CPP_XIOS
     426    CALL wxios_set_context
     427#endif
    424428
    425429    DO ilev=1,klev
     
    19541958            IF (type_trac == 'lmdz' .OR. type_trac == 'repr' .OR. type_trac == 'coag') THEN
    19551959             !--3D fields
    1956              CALL histwrite_phy(o_trac(iq-nqo), tr_seri(:,:,iq-nqo))
    1957              CALL histwrite_phy(o_dtr_vdf(iq-nqo),d_tr_cl(:,:,iq-nqo))
    1958              CALL histwrite_phy(o_dtr_the(iq-nqo),d_tr_th(:,:,iq-nqo))
    1959              CALL histwrite_phy(o_dtr_con(iq-nqo),d_tr_cv(:,:,iq-nqo))
    1960              CALL histwrite_phy(o_dtr_lessi_impa(iq-nqo),d_tr_lessi_impa(:,:,iq-nqo))
    1961              CALL histwrite_phy(o_dtr_lessi_nucl(iq-nqo),d_tr_lessi_nucl(:,:,iq-nqo))
    1962              CALL histwrite_phy(o_dtr_insc(iq-nqo),d_tr_insc(:,:,iq-nqo))
    1963              CALL histwrite_phy(o_dtr_bcscav(iq-nqo),d_tr_bcscav(:,:,iq-nqo))
    1964              CALL histwrite_phy(o_dtr_evapls(iq-nqo),d_tr_evapls(:,:,iq-nqo))
    1965              CALL histwrite_phy(o_dtr_ls(iq-nqo),d_tr_ls(:,:,iq-nqo))
    1966              CALL histwrite_phy(o_dtr_trsp(iq-nqo),d_tr_trsp(:,:,iq-nqo))
    1967              CALL histwrite_phy(o_dtr_sscav(iq-nqo),d_tr_sscav(:,:,iq-nqo))
    1968              CALL histwrite_phy(o_dtr_sat(iq-nqo),d_tr_sat(:,:,iq-nqo))
    1969              CALL histwrite_phy(o_dtr_uscav(iq-nqo),d_tr_uscav(:,:,iq-nqo))
     1960!             CALL histwrite_phy(o_trac(iq-nqo), tr_seri(:,:,iq-nqo))
     1961!             CALL histwrite_phy(o_dtr_vdf(iq-nqo),d_tr_cl(:,:,iq-nqo))
     1962!             CALL histwrite_phy(o_dtr_the(iq-nqo),d_tr_th(:,:,iq-nqo))
     1963!             CALL histwrite_phy(o_dtr_con(iq-nqo),d_tr_cv(:,:,iq-nqo))
     1964!             CALL histwrite_phy(o_dtr_lessi_impa(iq-nqo),d_tr_lessi_impa(:,:,iq-nqo))
     1965!             CALL histwrite_phy(o_dtr_lessi_nucl(iq-nqo),d_tr_lessi_nucl(:,:,iq-nqo))
     1966!             CALL histwrite_phy(o_dtr_insc(iq-nqo),d_tr_insc(:,:,iq-nqo))
     1967!             CALL histwrite_phy(o_dtr_bcscav(iq-nqo),d_tr_bcscav(:,:,iq-nqo))
     1968!             CALL histwrite_phy(o_dtr_evapls(iq-nqo),d_tr_evapls(:,:,iq-nqo))
     1969!             CALL histwrite_phy(o_dtr_ls(iq-nqo),d_tr_ls(:,:,iq-nqo))
     1970!             CALL histwrite_phy(o_dtr_trsp(iq-nqo),d_tr_trsp(:,:,iq-nqo))
     1971!             CALL histwrite_phy(o_dtr_sscav(iq-nqo),d_tr_sscav(:,:,iq-nqo))
     1972!             CALL histwrite_phy(o_dtr_sat(iq-nqo),d_tr_sat(:,:,iq-nqo))
     1973!             CALL histwrite_phy(o_dtr_uscav(iq-nqo),d_tr_uscav(:,:,iq-nqo))
    19701974             !--2D fields
    1971              CALL histwrite_phy(o_dtr_dry(iq-nqo), flux_tr_dry(:,iq-nqo))
     1975!             CALL histwrite_phy(o_dtr_dry(iq-nqo), flux_tr_dry(:,iq-nqo))
    19721976             zx_tmp_fi2d=0.
    19731977             IF (vars_defined) THEN
     
    19761980                ENDDO
    19771981             ENDIF
    1978              CALL histwrite_phy(o_trac_cum(iq-nqo), zx_tmp_fi2d)
     1982!             CALL histwrite_phy(o_trac_cum(iq-nqo), zx_tmp_fi2d)
    19791983            ENDIF
    19801984          ENDDO
  • LMDZ6/branches/DYNAMICO-conv/libf/phylmd/physiq_mod.F90

    r3322 r3336  
    2525    USE dimphy
    2626    USE infotrac_phy, ONLY: nqtot, nbtr, nqo, type_trac
    27     USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, nbp_lev, klon_glo
     27    USE mod_grid_phy_lmdz, ONLY: nbp_lon, nbp_lat, nbp_lev, klon_glo, grid1dTo2d_glo, grid_type, unstructured
    2828    USE mod_phys_lmdz_para
    2929    USE iophy
     
    252252    use ACAMA_GWD_rando_m, only: ACAMA_GWD_rando
    253253    USE VERTICAL_LAYERS_MOD, ONLY: aps,bps
     254    USE etat0_limit_unstruct_mod
     255#ifdef CPP_XIOS
     256    USE xios, ONLY: xios_update_calendar, xios_context_finalize
     257#endif
     258    USE climoz_mod
     259    USE limit_read_mod, ONLY : init_limit_read
    254260
    255261
     
    11291135    CALL update_time(pdtphys)
    11301136    phys_tstep=NINT(pdtphys)
     1137#ifdef CPP_XIOS
     1138    IF (.NOT. debut .AND. is_omp_master) CALL xios_update_calendar(itap+1)
     1139#endif
    11311140
    11321141    !======================================================================
     
    11611170
    11621171    IF (first) THEN
     1172       CALL init_etat0_limit_unstruct
     1173       IF (.NOT. create_etat0_limit) CALL init_limit_read(days_elapsed)
    11631174       !CR:nvelles variables convection/poches froides
    11641175
     
    13941405       CALL init_iophy_new(latitude_deg,longitude_deg)
    13951406
     1407          !===================================================================
     1408          !IM stations CFMIP
     1409          nCFMIP=npCFMIP
     1410          OPEN(98,file='npCFMIP_param.data',status='old', &
     1411               form='formatted',iostat=iostat)
     1412          IF (iostat == 0) THEN
     1413             READ(98,*,end=998) nCFMIP
     1414998          CONTINUE
     1415             CLOSE(98)
     1416             CONTINUE
     1417             IF(nCFMIP.GT.npCFMIP) THEN
     1418                print*,'nCFMIP > npCFMIP : augmenter npCFMIP et recompiler'
     1419                CALL abort_physic("physiq", "", 1)
     1420             ELSE
     1421                print*,'physiq npCFMIP=',npCFMIP,'nCFMIP=',nCFMIP
     1422             ENDIF
     1423
     1424             !
     1425             ALLOCATE(tabCFMIP(nCFMIP))
     1426             ALLOCATE(lonCFMIP(nCFMIP), latCFMIP(nCFMIP))
     1427             ALLOCATE(tabijGCM(nCFMIP))
     1428             ALLOCATE(lonGCM(nCFMIP), latGCM(nCFMIP))
     1429             ALLOCATE(iGCM(nCFMIP), jGCM(nCFMIP))
     1430             !
     1431             ! lecture des nCFMIP stations CFMIP, de leur numero
     1432             ! et des coordonnees geographiques lonCFMIP, latCFMIP
     1433             !
     1434             CALL read_CFMIP_point_locations(nCFMIP, tabCFMIP,  &
     1435                  lonCFMIP, latCFMIP)
     1436             !
     1437             ! identification des
     1438             ! 1) coordonnees lonGCM, latGCM des points CFMIP dans la
     1439             ! grille de LMDZ
     1440             ! 2) indices points tabijGCM de la grille physique 1d sur
     1441             ! klon points
     1442             ! 3) indices iGCM, jGCM de la grille physique 2d
     1443             !
     1444             CALL LMDZ_CFMIP_point_locations(nCFMIP, lonCFMIP, latCFMIP, &
     1445                  tabijGCM, lonGCM, latGCM, iGCM, jGCM)
     1446             !
     1447          ELSE
     1448             ALLOCATE(tabijGCM(0))
     1449             ALLOCATE(lonGCM(0), latGCM(0))
     1450             ALLOCATE(iGCM(0), jGCM(0))
     1451          ENDIF
     1452
     1453#ifdef CPP_IOIPSL
     1454
     1455       !$OMP MASTER
     1456       ! FH : if ok_sync=.true. , the time axis is written at each time step
     1457       ! in the output files. Only at the end in the opposite case
     1458       ok_sync_omp=.false.
     1459       CALL getin('ok_sync',ok_sync_omp)
     1460       CALL phys_output_open(longitude_deg,latitude_deg,nCFMIP,tabijGCM, &
     1461            iGCM,jGCM,lonGCM,latGCM, &
     1462            jjmp1,nlevSTD,clevSTD,rlevSTD, phys_tstep,ok_veget, &
     1463            type_ocean,iflag_pbl,iflag_pbl_split,ok_mensuel,ok_journe, &
     1464            ok_hf,ok_instan,ok_LES,ok_ade,ok_aie, &
     1465            read_climoz, phys_out_filestations, &
     1466            new_aod, aerosol_couple, &
     1467            flag_aerosol_strat, pdtphys, paprs, pphis,  &
     1468            pplay, lmax_th, ptconv, ptconvth, ivap,  &
     1469            d_u, d_t, qx, d_qx, zmasse, ok_sync_omp)
     1470       !$OMP END MASTER
     1471       !$OMP BARRIER
     1472       ok_sync=ok_sync_omp
     1473
     1474       freq_outNMC(1) = ecrit_files(7)
     1475       freq_outNMC(2) = ecrit_files(8)
     1476       freq_outNMC(3) = ecrit_files(9)
     1477       WRITE(lunout,*)'OK freq_outNMC(1)=',freq_outNMC(1)
     1478       WRITE(lunout,*)'OK freq_outNMC(2)=',freq_outNMC(2)
     1479       WRITE(lunout,*)'OK freq_outNMC(3)=',freq_outNMC(3)
     1480
     1481#ifndef CPP_XIOS
     1482       CALL ini_paramLMDZ_phy(phys_tstep,nid_ctesGCM)
     1483#endif
     1484
     1485#endif
     1486       ecrit_reg = ecrit_reg * un_jour
     1487       ecrit_tra = ecrit_tra * un_jour
     1488
     1489       !XXXPB Positionner date0 pour initialisation de ORCHIDEE
     1490       date0 = jD_ref
     1491       WRITE(*,*) 'physiq date0 : ',date0
     1492       !
     1493
     1494       CALL create_climoz(read_climoz)
     1495
     1496       CALL phys_output_write(itap, pdtphys, paprs, pphis,                    &
     1497                              pplay, lmax_th, aerosol_couple,                 &
     1498                              ok_ade, ok_aie, ivap, iliq, isol, new_aod, ok_sync,&
     1499                              ptconv, read_climoz, clevSTD,                   &
     1500                              ptconvth, d_u, d_t, qx, d_qx, zmasse,           &
     1501                              flag_aerosol, flag_aerosol_strat, ok_cdnc)
     1502
     1503#ifdef CPP_XIOS
     1504       IF (is_omp_master) CALL xios_update_calendar(1)
     1505#endif
     1506       CALL create_etat0_limit_unstruct
    13961507
    13971508       CALL phyetat0 ("startphy.nc",clesphy0,tabcntr0)
     1509
    13981510!jyg<
    13991511       IF (klon_glo==1) THEN
     
    15061618          !        enddo
    15071619
    1508           !===================================================================
    1509           !IM stations CFMIP
    1510           nCFMIP=npCFMIP
    1511           OPEN(98,file='npCFMIP_param.data',status='old', &
    1512                form='formatted',iostat=iostat)
    1513           IF (iostat == 0) THEN
    1514              READ(98,*,end=998) nCFMIP
    1515 998          CONTINUE
    1516              CLOSE(98)
    1517              CONTINUE
    1518              IF(nCFMIP.GT.npCFMIP) THEN
    1519                 print*,'nCFMIP > npCFMIP : augmenter npCFMIP et recompiler'
    1520                 CALL abort_physic("physiq", "", 1)
    1521              ELSE
    1522                 print*,'physiq npCFMIP=',npCFMIP,'nCFMIP=',nCFMIP
    1523              ENDIF
    1524 
    1525              !
    1526              ALLOCATE(tabCFMIP(nCFMIP))
    1527              ALLOCATE(lonCFMIP(nCFMIP), latCFMIP(nCFMIP))
    1528              ALLOCATE(tabijGCM(nCFMIP))
    1529              ALLOCATE(lonGCM(nCFMIP), latGCM(nCFMIP))
    1530              ALLOCATE(iGCM(nCFMIP), jGCM(nCFMIP))
    1531              !
    1532              ! lecture des nCFMIP stations CFMIP, de leur numero
    1533              ! et des coordonnees geographiques lonCFMIP, latCFMIP
    1534              !
    1535              CALL read_CFMIP_point_locations(nCFMIP, tabCFMIP,  &
    1536                   lonCFMIP, latCFMIP)
    1537              !
    1538              ! identification des
    1539              ! 1) coordonnees lonGCM, latGCM des points CFMIP dans la
    1540              ! grille de LMDZ
    1541              ! 2) indices points tabijGCM de la grille physique 1d sur
    1542              ! klon points
    1543              ! 3) indices iGCM, jGCM de la grille physique 2d
    1544              !
    1545              CALL LMDZ_CFMIP_point_locations(nCFMIP, lonCFMIP, latCFMIP, &
    1546                   tabijGCM, lonGCM, latGCM, iGCM, jGCM)
    1547              !
    1548           ELSE
    1549              ALLOCATE(tabijGCM(0))
    1550              ALLOCATE(lonGCM(0), latGCM(0))
    1551              ALLOCATE(iGCM(0), jGCM(0))
    1552           ENDIF
    1553        ELSE
    1554           ALLOCATE(tabijGCM(0))
    1555           ALLOCATE(lonGCM(0), latGCM(0))
    1556           ALLOCATE(iGCM(0), jGCM(0))
     1620       !ELSE
     1621       !   ALLOCATE(tabijGCM(0))
     1622       !   ALLOCATE(lonGCM(0), latGCM(0))
     1623       !   ALLOCATE(iGCM(0), jGCM(0))
    15571624       ENDIF
    15581625
     
    16421709#endif
    16431710
    1644 #ifdef CPP_IOIPSL
    1645 
    1646        !$OMP MASTER
    1647        ! FH : if ok_sync=.true. , the time axis is written at each time step
    1648        ! in the output files. Only at the end in the opposite case
    1649        ok_sync_omp=.false.
    1650        CALL getin('ok_sync',ok_sync_omp)
    1651        CALL phys_output_open(longitude_deg,latitude_deg,nCFMIP,tabijGCM, &
    1652             iGCM,jGCM,lonGCM,latGCM, &
    1653             jjmp1,nlevSTD,clevSTD,rlevSTD, phys_tstep,ok_veget, &
    1654             type_ocean,iflag_pbl,iflag_pbl_split,ok_mensuel,ok_journe, &
    1655             ok_hf,ok_instan,ok_LES,ok_ade,ok_aie, &
    1656             read_climoz, phys_out_filestations, &
    1657             new_aod, aerosol_couple, &
    1658             flag_aerosol_strat, pdtphys, paprs, pphis,  &
    1659             pplay, lmax_th, ptconv, ptconvth, ivap,  &
    1660             d_u, d_t, qx, d_qx, zmasse, ok_sync_omp)
    1661        !$OMP END MASTER
    1662        !$OMP BARRIER
    1663        ok_sync=ok_sync_omp
    1664 
    1665        freq_outNMC(1) = ecrit_files(7)
    1666        freq_outNMC(2) = ecrit_files(8)
    1667        freq_outNMC(3) = ecrit_files(9)
    1668        WRITE(lunout,*)'OK freq_outNMC(1)=',freq_outNMC(1)
    1669        WRITE(lunout,*)'OK freq_outNMC(2)=',freq_outNMC(2)
    1670        WRITE(lunout,*)'OK freq_outNMC(3)=',freq_outNMC(3)
    1671 
    1672 #ifndef CPP_XIOS
    1673        CALL ini_paramLMDZ_phy(phys_tstep,nid_ctesGCM)
    1674 #endif
    1675 
    1676 #endif
    1677        ecrit_reg = ecrit_reg * un_jour
    1678        ecrit_tra = ecrit_tra * un_jour
    1679 
    1680        !XXXPB Positionner date0 pour initialisation de ORCHIDEE
    1681        date0 = jD_ref
    1682        WRITE(*,*) 'physiq date0 : ',date0
     1711
     1712       CALL printflag( tabcntr0,radpas,ok_journe, &
     1713            ok_instan, ok_region )
    16831714       !
    16841715       !
     
    47054736       ENDIF
    47064737       !$OMP END MASTER
     4738#ifdef CPP_XIOS
     4739       IF (is_omp_master) CALL xios_context_finalize
     4740#endif
    47074741    ENDIF
    47084742
  • LMDZ6/branches/DYNAMICO-conv/libf/phylmd/slab_heat_transp_mod.F90

    r3326 r3336  
    8484                                  aire_,apoln_,apols_, &
    8585                                  aireu_,airev_,rlatv, rad, omeg)
    86 !    USE comconst_mod, ONLY: omeg, rad
    8786    ! number of points in lon, lat
    8887    IMPLICIT NONE
Note: See TracChangeset for help on using the changeset viewer.