Changeset 3632


Ignore:
Timestamp:
Feb 19, 2025, 2:26:32 PM (5 months ago)
Author:
afalco
Message:

Pluto: OpenMP fixes.
AF

Location:
trunk/LMDZ.PLUTO/libf/phypluto
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.PLUTO/libf/phypluto/aerosol_mod.F90

    r3572 r3632  
    2929      use tracer_h
    3030      use comcstfi_mod, only: r, pi
     31      use mod_phys_lmdz_para, only : is_master
    3132
    3233!-----------------------------------------------------------------------
     
    4647      integer :: iaer,l,ig,ifine
    4748
    48       LOGICAL firstcall
    49       SAVE firstcall
    50       DATA firstcall/.true./
     49      LOGICAL,SAVE :: firstcall=.true.
     50!$OMP THREADPRIVATE(firstcall)
    5151
    5252      !!read altitudes and haze mmrs
     
    5656      character(len=100) :: file_path
    5757      character(len=100) :: file_name
    58       real,save :: levdat(Nfine),densdat(Nfine)
     58    !   real,save :: levdat(Nfine),densdat(Nfine)
     59      real,save,allocatable :: levdat(:)
     60      real,save,allocatable :: densdat(:)
    5961
    6062!---------------- INPUT ------------------------------------------------
     
    7476        endif
    7577
    76         file_path=trim(datadir)//'/haze_prop/'//file_name
    77         open(224,file=file_path,form='formatted')
    78         do ifine=1,Nfine
    79            read(224,*) levdat(ifine), densdat(ifine)
    80         enddo
    81         close(224)
    82         print*, 'Read Haze profile: ',file_path
     78        if (is_master) then
     79            if(.not.allocated(levdat)) then
     80                allocate(levdat(Nfine))
     81            endif
     82            if(.not.allocated(densdat)) then
     83                allocate(densdat(Nfine))
     84            endif
     85
     86
     87            file_path=trim(datadir)//'/haze_prop/'//file_name
     88            open(224,file=file_path,form='formatted')
     89            do ifine=1,Nfine
     90            read(224,*) levdat(ifine), densdat(ifine)
     91            enddo
     92            close(224)
     93            print*, 'Read Haze profile: ',file_path
     94        endif
     95!$OMP BARRIER
    8396      ENDIF
    8497
  • trunk/LMDZ.PLUTO/libf/phypluto/lymalpha.F90

    r3613 r3632  
    22      use datafile_mod
    33      use comcstfi_mod, only: pi
    4       use mod_phys_lmdz_para, only : is_master, bcast
     4      use mod_phys_lmdz_para, only : is_master
    55
    66      implicit none
     
    4343      integer ifine
    4444      character(len=100) :: file_path
    45       real,save :: lsdat(Nfine),fluxdat(Nfine)
    46 !$OMP THREADPRIVATE(lsdat,fluxdat)
     45      ! real,save :: lsdat(Nfine),fluxdat(Nfine)
     46      real,save,allocatable :: lsdat(:)
     47      real,save,allocatable :: fluxdat(:)
    4748
    4849
     
    5051
    5152      IF (firstcall) then
    52         firstcall=.false.
    53         file_path=trim(datadir)//'/sol_uv_flux.txt'
    54         if (is_master) print*,file_path
    55         open(222,file=file_path,form='formatted')
     53         firstcall=.false.
    5654
    57         if (is_master) then
    58         do ifine=1,Nfine
    59            read(222,*) lsdat(ifine), fluxdat(ifine)
    60         enddo
    61         close(222)
    62         endif ! is_master
     55!$OMP MASTER
     56         file_path=trim(datadir)//'/sol_uv_flux.txt'
     57         if (is_master) print*,file_path
    6358
    64         call bcast(lsdat)
    65         call bcast(fluxdat)
     59         open(222,file=file_path,form='formatted')
     60
     61            if(.not.allocated(lsdat)) then
     62               allocate(lsdat(Nfine))
     63            endif
     64            if(.not.allocated(fluxdat)) then
     65               allocate(fluxdat(Nfine))
     66            endif
     67
     68            do ifine=1,Nfine
     69               read(222,*) lsdat(ifine), fluxdat(ifine)
     70            enddo
     71            close(222)
     72
     73!$OMP END MASTER
     74!$OMP BARRIER
    6675      ENDIF
    67 
    6876
    6977      CALL interp_line(lsdat,fluxdat,Nfine,pls*180./pi,pflux,1)
  • trunk/LMDZ.PLUTO/libf/phypluto/physiq_mod.F90

    r3627 r3632  
    116116!         II.2.b Option 2 : Atmosphere has no radiative effect.
    117117!
    118 !      III. Vertical diffusion (turbulent mixing) 
     118!      III. Vertical diffusion (turbulent mixing)
    119119!
    120120!      IV. Convection :
     
    476476
    477477      ! local variables for skin depth check
    478       real :: therm_inertia(ngrid,nsoilmx)
     478      real :: therm_inertia(ngrid,nsoilmx)
     479    !   real :: tidat_out(ngrid,nsoilmx)
    479480      real :: inertia_min,inertia_max
    480481      real :: diurnal_skin ! diurnal skin depth (m)
     
    13011302                   qsurf(:,igcm_ch4_ice),dqsurf(:,igcm_ch4_ice), &
    13021303                   ptimestep,pplev,zdqch4fast,zdqsch4fast,'CH4',' vdifc ')
    1303         else 
     1304        else
    13041305             call testconserv(ngrid,nlayer,nq,pq,pdq,qsurf,dqsurf, &
    13051306                   igcm_ch4_gas,igcm_ch4_ice, &
     
    14041405                   qsurf(:,igcm_ch4_ice),dqsurf(:,igcm_ch4_ice), &
    14051406                   ptimestep,pplev,zdqch4fast,zdqsch4fast,'CH4',' n2cond')
    1406         else 
     1407        else
    14071408             call testconserv(ngrid,nlayer,nq,pq,pdq,qsurf,dqsurf, &
    14081409                   igcm_ch4_gas,igcm_ch4_ice, &
     
    15041505
    15051506            pdqmufi(:,:,:) = 0.
    1506    
     1507
    15071508            call calmufi(ptimestep,pplev,zzlev,pplay,zzlay,gzlat,pt,pq,pdq,pdqmufi_prod,pdqmufi)
    1508    
     1509
    15091510            pdq(:,:,:) = pdq(:,:,:) + pdqmufi(:,:,:)
    1510            
     1511
    15111512         ELSE
    15121513            IF (haze) THEN
     
    16901691
    16911692      ! ! For output :
    1692       ! tidat_out(:,:)=0.
    1693       ! DO l=1,min(nlayermx,nsoilmx)
    1694       !    tidat_out(:,l)=inertiedat(:,l)
    1695       ! ENDDO
     1693    tidat_out(:,:)=0.
     1694    !   DO l=1,nsoilmx
     1695    !      tidat_out(:,l)=therm_inertia(:,l)
     1696    ENDDO
    16961697
    16971698      ! Test energy conservation
     
    21422143         call write_output("capcal","capcal","W.s m-2 K-1",capcal)
    21432144         call write_output("tsoil","tsoil","K",tsoil)
    2144       endif
     2145         call write_output("therm_inertia","therm_inertia","S.I.",therm_inertia)
     2146      endif
    21452147
    21462148      ! Total energy balance diagnostics
     
    23472349            call write_output("rcs","Spherical mode characteristic radius","m",mp2m_rc_sph(:,:))
    23482350            call write_output("rcf","Fractal mode characteristic radius","m",mp2m_rc_fra(:,:))
    2349            
     2351
    23502352           if (optichaze) then
    23512353              call write_output("tau_col",&
Note: See TracChangeset for help on using the changeset viewer.