Changeset 847 for trunk/LMDZ.COMMON/libf


Ignore:
Timestamp:
Nov 18, 2012, 7:15:08 PM (12 years ago)
Author:
aslmd
Message:

LMDZ.COMMON. Corrected bugs with using variable cp in parallel. Corrected bugs related to problems when no tracers are used. Updated makelmdz_fcm with the latest version and added a few lines necessary for generic physics. Added a build_gcm script in csh. Updated AMD64_CICLAD compilation settings. Uploaded arch files to make the model work with ifort on ciclad.

Location:
trunk/LMDZ.COMMON/libf/dyn3dpar
Files:
3 edited

Legend:

Unmodified
Added
Removed
  • trunk/LMDZ.COMMON/libf/dyn3dpar/calfis_p.F

    r841 r847  
    357357
    358358! ADAPTATION GCM POUR CP(T)
    359          call tpot2t_p(ngridmx*llm,zteta,ztfi,zpk)
     359         call tpot2t_p(klon,llm,zteta,ztfi,zpk)
    360360
    361361c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
     
    984984     
    985985! ADAPTATION GCM POUR CP(T)
    986       call t2tpot_p(ngridmx,llm,ztfi,zteta,zpk)
     986      call t2tpot_p(klon,llm,ztfi,zteta,zpk)
    987987
    988988
  • trunk/LMDZ.COMMON/libf/dyn3dpar/cpdet.F

    r37 r847  
    109109      integer :: ij,l,ijb,ije
    110110     
    111       ijb=ij_begin
    112       ije=ij_end 
    113      
     111      !ijb=ij_begin
     112      !ije=ij_end
     113      ijb=1
     114      ije=ip1jmp1
     115     
    114116      if (planet_type.eq."venus") then
    115117!$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
     
    165167c======================================================================
    166168c======================================================================
    167       SUBROUTINE tpot2t_p(ip1jmp1,llm,yteta, yt, ypk)
     169      SUBROUTINE tpot2t_p(ip1jmp1,llm,yteta,yt,ypk)
    168170! Parallel version of tpot2t
    169171      USE parallel
     
    177179      real,intent(in) :: yteta(ip1jmp1,llm)
    178180      real,intent(in) :: ypk(ip1jmp1,llm)
     181
    179182! local variable:
    180183      integer :: ij,l,ijb,ije
    181      
    182       ijb=ij_begin
    183       ije=ij_end 
     184
     185      !ijb=ij_begin
     186      !ije=ij_end
     187      ijb=1
     188      ije=ip1jmp1
    184189
    185190      if (planet_type.eq."venus") then
  • trunk/LMDZ.COMMON/libf/dyn3dpar/leapfrog_p.F

    r841 r847  
    521521!         call Register_SwapFieldHallo(finvmaold,finvmaold,ip1jmp1,llm,
    522522!     &                                jj_Nb_caldyn,0,0,TestRequest)
    523  
     523
    524524        do j=1,nqtot
    525525         call Register_SwapFieldHallo(q(1,1,j),q(1,1,j),ip1jmp1,llm,
     
    610610        call WriteField_p('pkf',reshape(pkf,(/iip1,jmp1,llm/)))
    611611        call WriteField_p('phis',reshape(phis,(/iip1,jmp1/)))
     612        if (nqtot > 0) then
    612613        do j=1,nqtot
    613614          call WriteField_p('q'//trim(int2str(j)),
    614615     .                reshape(q(:,:,j),(/iip1,jmp1,llm/)))
    615616        enddo
     617        endif
    616618!$OMP END MASTER       
    617619c$OMP BARRIER
     
    939941     *                      1,0,0,1,Request_physic)
    940942
     943        if (nqtot > 0) then
    941944        do j=1,nqtot
    942945          call Register_Hallo(dqfi(1,1,j),ip1jmp1,llm,
    943946     *                        1,0,0,1,Request_physic)
    944947        enddo
     948        endif
    945949       
    946950        call SendRequest(Request_Physic)
     
    10581062c
    10591063c  Diagnostique de conservation de l'energie : difference
    1060       IF (ip_ebil_dyn.ge.1 ) THEN
     1064      IF ((ip_ebil_dyn.ge.1 ) .and. (nqtot > 1)) THEN
    10611065          ztit='bil phys'
    10621066          CALL diagedyn(ztit,2,1,1,dtphys
     
    14991503                write(82,*) 'ps',ps
    15001504                write(83,*) 'q',q
    1501                 WRITE(85,*) 'q1 = ',q(:,:,1)
    1502                 WRITE(86,*) 'q3 = ',q(:,:,3)
     1505                if (nqtot > 2) then
     1506                 WRITE(85,*) 'q1 = ',q(:,:,1)
     1507                 WRITE(86,*) 'q3 = ',q(:,:,3)
     1508                endif
    15031509              endif
    15041510 
     
    15541560                call Gather_Field(pk,ip1jmp1,llm,0)
    15551561                call Gather_Field(phi,ip1jmp1,llm,0)
    1556                 do iq=1,nqtot
     1562                 do iq=1,nqtot
    15571563                  call Gather_Field(q(1,1,iq),ip1jmp1,llm,0)
    1558                 enddo
     1564                 enddo
    15591565                call Gather_Field(masse,ip1jmp1,llm,0)
    15601566                call Gather_Field(ps,ip1jmp1,1,0)
     
    16261632                call Gather_Field(teta,ip1jmp1,llm,0)
    16271633                call Gather_Field(phi,ip1jmp1,llm,0)
    1628                 do iq=1,nqtot
     1634                 do iq=1,nqtot
    16291635                  call Gather_Field(q(1,1,iq),ip1jmp1,llm,0)
    1630                 enddo
     1636                 enddo
    16311637                call Gather_Field(masse,ip1jmp1,llm,0)
    16321638                call Gather_Field(ps,ip1jmp1,1,0)
     
    18501856                call Gather_Field(teta,ip1jmp1,llm,0)
    18511857                call Gather_Field(phi,ip1jmp1,llm,0)
    1852                 do iq=1,nqtot
     1858                 do iq=1,nqtot
    18531859                  call Gather_Field(q(1,1,iq),ip1jmp1,llm,0)
    1854                 enddo
     1860                 enddo
    18551861                call Gather_Field(masse,ip1jmp1,llm,0)
    18561862                call Gather_Field(ps,ip1jmp1,1,0)
     
    18691875                  call Gather_Field(teta,ip1jmp1,llm,0)
    18701876                  call Gather_Field(ps,ip1jmp1,1,0)
    1871                   do iq=1,nqtot
     1877                   do iq=1,nqtot
    18721878                    call Gather_Field(q(1,1,iq),ip1jmp1,llm,0)
    1873                   enddo
     1879                   enddo
    18741880c     
    18751881                  if (mpi_rank==0) then
Note: See TracChangeset for help on using the changeset viewer.