Changeset 2475


Ignore:
Timestamp:
Mar 22, 2016, 1:19:13 PM (8 years ago)
Author:
Ehouarn Millour
Message:

Reinstate writehist, writedyn and bilan_dyn in dyn3dmem so that ouputs in the dynamics (dyn_hist* and dynzon files) may be generated when in parallel.
EM

Location:
LMDZ5/trunk/libf
Files:
8 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dyn3d/leapfrog.F

    r2375 r2475  
    686686               ENDIF
    687687               
     688!              ! Ehouarn: re-compute geopotential for outputs
     689               CALL geopot(ip1jmp1,teta,pk,pks,phis,phi)
     690
    688691               IF (ok_dynzon) THEN
    689692#ifdef CPP_IOIPSL
     
    821824               ENDIF
    822825
     826!              ! Ehouarn: re-compute geopotential for outputs
     827               CALL geopot(ip1jmp1,teta,pk,pks,phis,phi)
     828
    823829               IF (ok_dynzon) THEN
    824830#ifdef CPP_IOIPSL
  • LMDZ5/trunk/libf/dyn3dmem/bilan_dyn_loc.F

    r1907 r2475  
    1616      USE mod_hallo
    1717      use misc_mod
    18       use write_field
     18      USE write_field_loc
    1919      IMPLICIT NONE
    2020
     
    171171     
    172172      INTEGER :: bilan_dyn_domain_id
    173 
    174173
    175174c=====================================================================
     
    216215      ALLOCATE(ndex3d(jjb_v:jje_v*llm))
    217216      ndex3d=0
    218       ALLOCATE(rlong(jjb_v:jje_v))
    219       ALLOCATE(rlatg(jjb_v:jje_v))
     217      ALLOCATE(rlong(1))
     218      ALLOCATE(rlatg(jjm))
    220219     
    221220!$OMP END MASTER
     
    285284       
    286285      call histbeg(trim(infile),
    287      .             1, rlong(jjb:jje), jjn, rlatg(jjb:jje),
     286     .             1, rlong, jjn, rlatg(jjb:jje),
    288287     .             1, 1, 1, jjn,
    289288     .             tau0, zjulian, dt_cum, thoriid, fileid,
     
    514513            enddo
    515514         enddo
    516 !$OMP END DO NOWAIT
    517       enddo
    518 
     515!$OMP ENDDO NOWAIT
     516!$OMP BARRIER
     517      enddo
    519518
    520519c    tendances
     
    540539      CALL vitvert_loc(convm,w)
    541540!$OMP BARRIER
     541
    542542
    543543      jjb=jj_begin
     
    618618!$OMP ENDDO NOWAIT
    619619         
    620      
    621620      IF (pole_sud) jje=jj_end-1
    622621!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
     
    626625      ENDDO
    627626!$OMP ENDDO NOWAIT
     627!$OMP BARRIER
    628628         
    629629      jjb=jj_begin
     
    640640!$OMP ENDDO NOWAIT
    641641      enddo
    642  
     642
    643643c=====================================================================
    644644c   Transport méridien
     
    657657        ENDDO
    658658!$OMP ENDDO NOWAIT
     659!$OMP BARRIER
    659660
    660661      call Register_Hallo_u(masse_cum,llm,1,1,1,1,Req)
     
    684685      enddo
    685686!$OMP ENDDO NOWAIT
     687!$OMP BARRIER
    686688
    687689c     print*,'3OK'
  • LMDZ5/trunk/libf/dyn3dmem/gcm.F90

    r2372 r2475  
    415415#ifdef CPP_IOIPSL
    416416  time_step = zdtvr
    417   IF (mpi_rank==0) then
    418417     if (ok_dyn_ins) then
    419418        ! initialize output file for instantaneous outputs
     
    421420        t_ops =((1.0*iecri)/day_step) * daysec 
    422421        t_wrt = daysec ! iecri * daysec ! write output every t_wrt
    423         t_wrt = daysec ! iecri * daysec ! write output every t_wrt
    424         CALL inithist(day_ref,annee_ref,time_step, &
     422        CALL inithist_loc(day_ref,annee_ref,time_step, &
    425423             t_ops,t_wrt)
    426424     endif
     
    432430        CALL initdynav_loc(day_ref,annee_ref,time_step,t_ops,t_wrt)
    433431     END IF
    434   ENDIF
    435432  dtav = iperiod*dtvr/daysec
    436433#endif
  • LMDZ5/trunk/libf/dyn3dmem/initdynav_loc.F

    r1907 r2475  
    154154
    155155      ddid=(/ 1,2 /)
    156       dsg=(/ iip1,jjp1 /)
     156      dsg=(/ iip1,jjm /)
    157157      dsl=(/ iip1,jjn /)
    158158      dpf=(/ 1,jjb /)
     
    171171     
    172172! Grille U
     173
     174      do jj = 1, jjp1
     175        do ii = 1, iip1
     176          rlong(ii,jj) = rlonu(ii) * 180. / pi
     177          rlat(ii,jj) = rlatu(jj) * 180. / pi
     178        enddo
     179      enddo
    173180
    174181      jjb=jj_begin
     
    209216C  Vents U
    210217C
     218      jjn=jj_nb
    211219      call histdef(histuaveid, 'u', 'vent u moyen ',
    212      .             'm/s', iip1, jjp1, uhoriid, llm, 1, llm, zvertiidu,
     220     .             'm/s', iip1, jjn, uhoriid, llm, 1, llm, zvertiidu,
    213221     .             32, 'ave(X)', t_ops, t_wrt)
    214222
     
    216224C  Vents V
    217225C
     226      if (pole_sud) jjn=jj_nb-1
    218227      call histdef(histvaveid, 'v', 'vent v moyen',
    219      .             'm/s', iip1, jjm, vhoriid, llm, 1, llm, zvertiidv,
     228     .             'm/s', iip1, jjn, vhoriid, llm, 1, llm, zvertiidv,
    220229     .             32, 'ave(X)', t_ops, t_wrt)
    221230
     
    223232C  Temperature
    224233C
     234      jjn=jj_nb
    225235      call histdef(histaveid, 'temp', 'temperature moyenne', 'K',
    226      .             iip1, jjp1, thoriid, llm, 1, llm, zvertiid,
     236     .             iip1, jjn, thoriid, llm, 1, llm, zvertiid,
    227237     .             32, 'ave(X)', t_ops, t_wrt)
    228238C
     
    230240C
    231241      call histdef(histaveid, 'theta', 'temperature potentielle', 'K',
    232      .             iip1, jjp1, thoriid, llm, 1, llm, zvertiid,
     242     .             iip1, jjn, thoriid, llm, 1, llm, zvertiid,
    233243     .             32, 'ave(X)', t_ops, t_wrt)
    234244
     
    238248C
    239249      call histdef(histaveid, 'phi', 'geopotentiel moyen', '-',
    240      .             iip1, jjp1, thoriid, llm, 1, llm, zvertiid,
     250     .             iip1, jjn, thoriid, llm, 1, llm, zvertiid,
    241251     .             32, 'ave(X)', t_ops, t_wrt)
    242252C
     
    251261C  Masse
    252262C
    253       call histdef(histaveid, 'masse', 'masse', 'kg',
    254      .             iip1, jjp1, thoriid, llm, 1, llm, zvertiid,
     263      call histdef(histaveid, 'masse', 'masse moyenne', 'kg',
     264     .             iip1, jjn, thoriid, llm, 1, llm, zvertiid,
    255265     .             32, 'ave(X)', t_ops, t_wrt)
    256266C
     
    258268C
    259269      call histdef(histaveid, 'ps', 'pression naturelle au sol', 'Pa',
    260      .             iip1, jjp1, thoriid, 1, 1, 1, -99,
    261      .             32, 'ave(X)', t_ops, t_wrt)
    262 C
    263 Pression au sol
     270     .             iip1, jjn, thoriid, 1, 1, 1, -99,
     271     .             32, 'ave(X)', t_ops, t_wrt)
     272C
     273Geopotentiel au sol
    264274C
    265275!      call histdef(histaveid, 'phis', 'geopotentiel au sol', '-',
     
    273283      call histend(histvaveid)
    274284#else
    275       write(lunout,*)'initdynav_p: Needs IOIPSL to function'
     285      write(lunout,*)'initdynav_loc: Needs IOIPSL to function'
    276286#endif
    277287! #endif of #ifdef CPP_IOIPSL
    278       return
    279288      end
  • LMDZ5/trunk/libf/dyn3dmem/inithist_loc.F

    r1907 r2475  
    153153
    154154      ddid=(/ 1,2 /)
    155       dsg=(/ iip1,jjp1 /)
     155      dsg=(/ iip1,jjm /)
    156156      dsl=(/ iip1,jjn /)
    157157      dpf=(/ 1,jjb /)
     
    170170     
    171171! Grille U
     172
     173      do jj = 1, jjp1
     174        do ii = 1, iip1
     175          rlong(ii,jj) = rlonu(ii) * 180. / pi
     176          rlat(ii,jj) = rlatu(jj) * 180. / pi
     177        enddo
     178      enddo
    172179
    173180      jjb=jj_begin
     
    210217C  Vents U
    211218C
    212       call histdef(histuid, 'u', 'vent u moyen ',
    213      .             'm/s', iip1, jjp1, uhoriid, llm, 1, llm, zvertiidu,
    214      .             32, 'ave(X)', t_ops, t_wrt)
     219      jjn=jj_nb
     220      call histdef(histuid, 'u', 'vent u',
     221     .             'm/s', iip1, jjn, uhoriid, llm, 1, llm, zvertiidu,
     222     .             32, 'inst(X)', t_ops, t_wrt)
    215223
    216224C
    217225C  Vents V
    218226C
    219       call histdef(histvid, 'v', 'vent v moyen',
    220      .             'm/s', iip1, jjm, vhoriid, llm, 1, llm, zvertiidv,
    221      .             32, 'ave(X)', t_ops, t_wrt)
     227      if (pole_sud) jjn=jj_nb-1
     228      call histdef(histvid, 'v', 'vent v',
     229     .             'm/s', iip1, jjn, vhoriid, llm, 1, llm, zvertiidv,
     230     .             32, 'inst(X)', t_ops, t_wrt)
    222231
    223232C
    224233C  Temperature
    225234C
    226       call histdef(histid, 'temp', 'temperature moyenne', 'K',
    227      .             iip1, jjp1, thoriid, llm, 1, llm, zvertiid,
    228      .             32, 'ave(X)', t_ops, t_wrt)
     235      jjn=jj_nb
     236      call histdef(histid, 'temp', 'temperature', 'K',
     237     .             iip1, jjn, thoriid, llm, 1, llm, zvertiid,
     238     .             32, 'inst(X)', t_ops, t_wrt)
    229239C
    230240C  Temperature potentielle
    231241C
    232242      call histdef(histid, 'theta', 'temperature potentielle', 'K',
    233      .             iip1, jjp1, thoriid, llm, 1, llm, zvertiid,
    234      .             32, 'ave(X)', t_ops, t_wrt)
     243     .             iip1, jjn, thoriid, llm, 1, llm, zvertiid,
     244     .             32, 'inst(X)', t_ops, t_wrt)
    235245
    236246
     
    238248C  Geopotentiel
    239249C
    240       call histdef(histid, 'phi', 'geopotentiel moyen', '-',
    241      .             iip1, jjp1, thoriid, llm, 1, llm, zvertiid,
    242      .             32, 'ave(X)', t_ops, t_wrt)
     250      call histdef(histid, 'phi', 'geopotentiel', '-',
     251     .             iip1, jjn, thoriid, llm, 1, llm, zvertiid,
     252     .             32, 'inst(X)', t_ops, t_wrt)
    243253C
    244254C  Traceurs
     
    247257!          call histdef(histid, ttext(iq), ttext(iq), '-',
    248258!     .             iip1, jjn, thoriid, llm, 1, llm, zvertiid,
    249 !     .             32, 'ave(X)', t_ops, t_wrt)
     259!     .             32, 'inst(X)', t_ops, t_wrt)
    250260!        enddo
    251261C
     
    253263C
    254264      call histdef(histid, 'masse', 'masse', 'kg',
    255      .             iip1, jjp1, thoriid, llm, 1, llm, zvertiid,
    256      .             32, 'ave(X)', t_ops, t_wrt)
     265     .             iip1, jjn, thoriid, llm, 1, llm, zvertiid,
     266     .             32, 'inst(X)', t_ops, t_wrt)
    257267C
    258268C  Pression au sol
    259269C
    260270      call histdef(histid, 'ps', 'pression naturelle au sol', 'Pa',
    261      .             iip1, jjp1, thoriid, 1, 1, 1, -99,
    262      .             32, 'ave(X)', t_ops, t_wrt)
    263 C
    264 Pression au sol
     271     .             iip1, jjn, thoriid, 1, 1, 1, -99,
     272     .             32, 'inst(X)', t_ops, t_wrt)
     273C
     274Geopotentiel au sol
    265275C
    266276!      call histdef(histid, 'phis', 'geopotentiel au sol', '-',
    267277!     .             iip1, jjn, thoriid, 1, 1, 1, -99,
    268 !     .             32, 'ave(X)', t_ops, t_wrt)
     278!     .             32, 'inst(X)', t_ops, t_wrt)
    269279C
    270280C  Fin
     
    274284      call histend(histvid)
    275285#else
    276       write(lunout,*)'initdynav_p: Needs IOIPSL to function'
     286      write(lunout,*)'inithist_loc: Needs IOIPSL to function'
    277287#endif
    278288! #endif of #ifdef CPP_IOIPSL
    279       return
    280289      end
  • LMDZ5/trunk/libf/dyn3dmem/leapfrog_loc.F

    r2375 r2475  
    16031603               ENDIF
    16041604
     1605              ! Ehouarn: re-compute geopotential for outputs
     1606c$OMP BARRIER
     1607c$OMP MASTER
     1608              CALL geopot_loc(ip1jmp1,teta,pk,pks,phis,phi)
     1609c$OMP END MASTER
     1610c$OMP BARRIER
     1611
    16051612#ifdef CPP_IOIPSL
    16061613             IF (ok_dynzon) THEN
     
    16381645#ifdef CPP_IOIPSL
    16391646             if (ok_dyn_ins) then
    1640                  CALL writehist_loc(itau,vcov,ucov,teta,phi,q,
     1647                 CALL writehist_loc(itau,vcov,ucov,teta,pk,phi,q,
    16411648     &                              masse,ps,phis)
    16421649             endif
     
    17501757
    17511758#ifdef CPP_IOIPSL
     1759              ! Ehouarn: re-compute geopotential for outputs
     1760c$OMP BARRIER
     1761c$OMP MASTER
     1762              CALL geopot_loc(ip1jmp1,teta,pk,pks,phis,phi)
     1763c$OMP END MASTER
     1764c$OMP BARRIER
     1765               
    17521766               IF (ok_dynzon) THEN
    17531767               CALL bilan_dyn_loc(2,dtvr*iperiod,dtvr*day_step*periodav,
     
    17741788#ifdef CPP_IOIPSL
    17751789              if (ok_dyn_ins) then
    1776                  CALL writehist_loc(itau,vcov,ucov,teta,phi,q,
     1790                 CALL writehist_loc(itau,vcov,ucov,teta,pk,phi,q,
    17771791     &                              masse,ps,phis)
    17781792              endif ! of if (ok_dyn_ins)
  • LMDZ5/trunk/libf/dyn3dmem/writedynav_loc.F

    r1907 r2475  
    8989!$OMP MASTER
    9090        ALLOCATE(unat(ijb_u:ije_u,llm))
    91         ALLOCATE(vnat(ijb_u:ije_u,llm))
     91        ALLOCATE(vnat(ijb_v:ije_v,llm))
    9292        ALLOCATE(tm(ijb_u:ije_u,llm))
    9393        ALLOCATE(ndex2d(ijnb_u*llm))
     
    127127C  Vents V
    128128C
    129 
     129      ije=ij_end
     130      if (pole_sud) jjn=jj_nb-1
     131      if (pole_sud) ije=ij_end-iip1
    130132!$OMP BARRIER
    131133!$OMP MASTER     
     
    138140C  Temperature potentielle moyennee
    139141C
     142      ijb=ij_begin
     143      ije=ij_end
     144      jjn=jj_nb
    140145!$OMP MASTER     
    141146      call histwrite(histaveid, 'theta', itau_w, teta(ijb:ije,:),
     
    186191!$OMP MASTER     
    187192       call histwrite(histaveid, 'masse', itau_w, masse(ijb:ije,:),
    188      .                iip1*jjn, ndexu)
     193     .                iip1*jjn*llm, ndexu)
    189194!$OMP END MASTER
    190195
     
    203208C
    204209!$OMP MASTER     
    205        call histwrite(histaveid, 'phis', itau_w, phis(ijb:ije),
    206      .                 iip1*jjn, ndexu)
     210!       call histwrite(histaveid, 'phis', itau_w, phis(ijb:ije),
     211!     .                 iip1*jjn, ndex2d)
    207212!$OMP END MASTER
    208213
     
    218223!$OMP END MASTER
    219224#else
    220       write(lunout,*)'writedynav_p: Needs IOIPSL to function'
     225      write(lunout,*)'writedynav_loc: Needs IOIPSL to function'
    221226#endif
    222227! #endif of #ifdef CPP_IOIPSL
    223       return
    224228      end
  • LMDZ5/trunk/libf/dyn3dmem/writehist_loc.F

    r1907 r2475  
    8989!$OMP MASTER
    9090        ALLOCATE(unat(ijb_u:ije_u,llm))
    91         ALLOCATE(vnat(ijb_u:ije_u,llm))
     91        ALLOCATE(vnat(ijb_v:ije_v,llm))
    9292        ALLOCATE(tm(ijb_u:ije_u,llm))
    9393        ALLOCATE(ndex2d(ijnb_u*llm))
     
    127127C  Vents V
    128128C
    129 
     129      ije=ij_end
     130      if (pole_sud) jjn=jj_nb-1
     131      if (pole_sud) ije=ij_end-iip1
    130132!$OMP BARRIER
    131133!$OMP MASTER     
     
    136138
    137139C
    138 C  Temperature potentielle moyennee
    139 C
     140C  Temperature potentielle
     141C
     142      ijb=ij_begin
     143      ije=ij_end
     144      jjn=jj_nb
    140145!$OMP MASTER     
    141146      call histwrite(histid, 'theta', itau_w, teta(ijb:ije,:),
     
    144149
    145150C
    146 C  Temperature moyennee
     151C  Temperature
    147152C
    148153
     
    186191!$OMP MASTER     
    187192       call histwrite(histid, 'masse', itau_w, masse(ijb:ije,:),
    188      .                iip1*jjn, ndexu)
     193     .                iip1*jjn*llm, ndexu)
    189194!$OMP END MASTER
    190195
     
    194199C
    195200!$OMP MASTER     
    196 
    197201       call histwrite(histid, 'ps', itau_w, ps(ijb:ije),
    198202     .                 iip1*jjn, ndex2d)
     
    203207C
    204208!$OMP MASTER     
    205        call histwrite(histid, 'phis', itau_w, phis(ijb:ije),
    206      .                 iip1*jjn, ndexu)
     209!       call histwrite(histid, 'phis', itau_w, phis(ijb:ije),
     210!     .                 iip1*jjn, ndex2d)
    207211!$OMP END MASTER
    208212
     
    218222!$OMP END MASTER
    219223#else
    220       write(lunout,*)'writedynav_p: Needs IOIPSL to function'
     224      write(lunout,*)'writehist_loc: Needs IOIPSL to function'
    221225#endif
    222226! #endif of #ifdef CPP_IOIPSL
    223       return
    224227      end
Note: See TracChangeset for help on using the changeset viewer.