Changeset 2281


Ignore:
Timestamp:
May 18, 2015, 11:09:37 AM (9 years ago)
Author:
crisi
Message:

Camille Risi: corrections of bugs for the isotopic part

Location:
LMDZ5/trunk/libf
Files:
11 edited

Legend:

Unmodified
Added
Removed
  • LMDZ5/trunk/libf/dyn3d/advtrac.F90

    r2270 r2281  
    225225
    226226     if (ok_iso_verif) then
    227            call check_isotopes_seq(q,1,ip1jmp1,'advtrac 162')
     227           write(*,*) 'advtrac 227'
     228           call check_isotopes_seq(q,ip1jmp1,'advtrac 162')
    228229     endif !if (ok_iso_verif) then
    229230
     
    399400
    400401     if (ok_iso_verif) then
     402           write(*,*) 'advtrac 402'
    401403           call check_isotopes_seq(q,ip1jmp1,'advtrac 397')
    402404     endif !if (ok_iso_verif) then
  • LMDZ5/trunk/libf/dyn3d/caladvtrac.F

    r2270 r2281  
    8585          ENDDO
    8686
     87          write(*,*) 'caladvtrac 87'
    8788          CALL qminimum( q, nqtot, finmasse )
     89          write(*,*) 'caladvtrac 89'
    8890
    8991          CALL SCOPY   ( ip1jmp1*llm, masse, 1, finmasse,       1 )
  • LMDZ5/trunk/libf/dyn3d/check_isotopes.F

    r2270 r2281  
    2929        if (ok_isotopes) then
    3030
     31        write(*,*) 'check_isotopes 31: err_msg=',err_msg
    3132        ! verifier que rien n'est NaN
    3233        do ixt=1,ntraciso
     
    4950        enddo !do ixt=1,ntraciso
    5051
     52        !write(*,*) 'check_isotopes 52'
    5153        ! verifier que l'eau normale est OK
    5254        if (use_iso(1)) then
     
    7476        endif !if (use_iso(1)) then
    7577       
     78        !write(*,*) 'check_isotopes 78'
    7679        ! verifier que HDO est raisonable
    7780        if (use_iso(2)) then
     
    98101        endif !if (use_iso(2)) then
    99102
     103        !write(*,*) 'check_isotopes 103'
    100104        ! verifier que O18 est raisonable
    101105        if (use_iso(3)) then
     
    123127
    124128
     129        !write(*,*) 'check_isotopes 129'
    125130        if (ok_isotrac) then
    126131
     
    191196
    192197        endif ! if (ok_isotopes)
     198        !write(*,*) 'check_isotopes 198'
    193199       
    194200        end
  • LMDZ5/trunk/libf/dyn3d/leapfrog.F

    r2270 r2281  
    344344     *        p, masse, dq,  teta,
    345345     .        flxw, pk)
     346          write(*,*) 'caladvtrac 346'
    346347
    347348         
  • LMDZ5/trunk/libf/dyn3d/qminimum.F

    r2270 r2281  
    152152       enddo !do k=2,llm
    153153
    154         if (ok_iso_verif) then
     154        if (ok_iso_verif) then     
    155155           call check_isotopes_seq(q,ip1jmp1,'qminimum 168')
    156156        endif !if (ok_iso_verif) then
     
    158158     
    159159        ! 3) transfert d'eau de la vapeur au liquide
    160         !write(*,*) 'qminimum 164'
     160        write(*,*) 'qminimum 164'
    161161        do k=1,llm
    162162        DO i = 1,ip1jmp1
     
    186186
    187187      endif !if (ok_isotopes) then
    188       !write(*,*) 'qminimum 188'
     188      write(*,*) 'qminimum 188'
    189189     
    190190c
  • LMDZ5/trunk/libf/dyn3dmem/check_isotopes_loc.F

    r2270 r2281  
    3030        if (ok_isotopes) then
    3131
     32        !write(*,*) 'check_isotopes 31: err_msg=',err_msg
    3233        ! verifier que rien n'est NaN
    3334        do ixt=1,ntraciso
    3435          do phase=1,nqo
    3536            iq=iqiso(ixt,phase)
     37c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    3638            do k=1,llm
    3739              DO i = ijb,ije
     
    4749              enddo !DO i = ijb,ije
    4850            enddo !do k=1,llm
     51c$OMP END DO NOWAIT
    4952          enddo !do phase=1,nqo
    5053        enddo !do ixt=1,ntraciso
    5154
     55        !write(*,*) 'check_isotopes 52'
    5256        ! verifier que l'eau normale est OK
    5357        if (use_iso(1)) then
     
    5559          do phase=1,nqo
    5660            iq=iqiso(ixt,phase)
     61c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    5762            do k=1,llm
    5863            DO i = ijb,ije 
     
    6368                  write(*,*) 'erreur detectee par iso_verif_egalite:'
    6469                  write(*,*) err_msg
    65                   write(*,*) 'ixt,phase=',ixt,phase
     70                  write(*,*) 'ixt,phase,ijb=',ixt,phase,ijb
    6671                  write(*,*) 'q,iq,i,k=',q(i,k,iq),iq,i,k
    6772                  write(*,*) 'q(i,k,phase)=',q(i,k,phase)
     
    7277            enddo ! DO i = ijb,ije
    7378            enddo !do k=1,llm
     79c$OMP END DO NOWAIT
    7480          enddo ! do phase=1,nqo
    7581        endif !if (use_iso(1)) then
    7682       
     83        !write(*,*) 'check_isotopes 78'
    7784        ! verifier que HDO est raisonable
    7885        if (use_iso(2)) then
     
    8087          do phase=1,nqo
    8188            iq=iqiso(ixt,phase)
     89c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    8290            do k=1,llm
    8391            DO i = ijb,ije
     
    96104            enddo !DO i = ijb,ije
    97105            enddo !do k=1,llm
     106c$OMP END DO NOWAIT
    98107          enddo ! do phase=1,nqo
    99108        endif !if (use_iso(2)) then
    100109
     110        !write(*,*) 'check_isotopes 103'
    101111        ! verifier que O18 est raisonable
    102112        if (use_iso(3)) then
     
    104114          do phase=1,nqo
    105115            iq=iqiso(ixt,phase)
     116c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    106117            do k=1,llm
    107118            DO i = ijb,ije
     
    120131            enddo !DO i = ijb,ije
    121132            enddo !do k=1,llm
     133c$OMP END DO NOWAIT
    122134          enddo ! do phase=1,nqo
    123135        endif !if (use_iso(2)) then
    124136
    125137
     138        !write(*,*) 'check_isotopes 129'
    126139        if (ok_isotrac) then
    127140
     
    133146               iq=iqiso(ixt,phase)
    134147               iqeau=iqiso(ieau,phase)
     148c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    135149               do k=1,llm
    136150                DO i = ijb,ije
     
    150164                enddo !DO i = ijb,ije
    151165                enddo  ! do k=1,llm
     166c$OMP END DO NOWAIT
    152167              enddo ! do phase=1,nqo   
    153168            enddo !do izone=1,ntraceurs_zone
     
    157172           do phase=1,nqo
    158173              iq=iqiso(iiso,phase)
     174c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
    159175              do k=1,llm
    160176                DO i = ijb,ije
     
    186202                enddo !DO i = ijb,ije
    187203              enddo !do k=1,llm
     204c$OMP END DO NOWAIT
    188205           enddo !do phase=1,nqo
    189206          enddo !do iiso=1,niso
     
    192209
    193210        endif ! if (ok_isotopes)
     211        !write(*,*) 'check_isotopes 198'
    194212       
    195213        end
  • LMDZ5/trunk/libf/dyn3dmem/integrd_loc.F

    r2270 r2281  
    8989      !write(*,*) 'integrd 88: entree, nq=',nq
    9090c-----------------------------------------------------------------------
    91 
    92         if (ok_iso_verif) then
    93            call check_isotopes(q,ijb,ije,'integrd 92')
    94         endif !if (ok_iso_verif) then
    9591
    9692c$OMP BARRIER     
     
    168164c$OMP END MASTER
    169165c$OMP BARRIER
     166        write(*,*) 'integrd 170'
    170167      IF (.NOT. Checksum_all) THEN
    171168        call WriteField_v('int_vcov',vcov)
     
    197194       
    198195c
     196        write(*,*) 'integrd 200'
    199197C$OMP MASTER
    200198      if (pole_nord) THEN
     
    287285c
    288286c
     287        write(*,*) 'integrd 291'
    289288      IF (pole_nord) THEN
    290289       
     
    353352        endif !if (ok_iso_verif) then
    354353
    355           !write(*,*) 'integrd 341'
    356           CALL qminimum_loc( q, nq, deltap )
    357           !write(*,*) 'integrd 343'
     354        write(*,*) 'integrd 341'
     355        CALL qminimum_loc( q, nq, deltap )
     356        write(*,*) 'integrd 343'
    358357
    359358        if (ok_iso_verif) then
  • LMDZ5/trunk/libf/dyn3dmem/vlsplt_loc.F

    r2277 r2281  
    4444      REAL u_mq(ijb_u:ije_u,llm)
    4545
    46       REAL masseq(ijb_u:ije_u,llm,nqtot),Ratio(ijb_u:ije_u,llm,nqtot) ! CRisi
     46      REAL Ratio(ijb_u:ije_u,llm,nqtot) ! CRisi
    4747      INTEGER ifils,iq2 ! CRisi
    4848
     
    341341           ! On a besoin de q et masse seulement entre ijb et ije. On ne
    342342           ! les calcule donc que de ijb à ije
    343            masseq(ij,l,iq2)=masse(ij,l,iq)*q(ij,l,iq)
     343           masse(ij,l,iq2)=masse(ij,l,iq)*q(ij,l,iq)
    344344           Ratio(ij,l,iq2)=q(ij,l,iq2)/q(ij,l,iq)
    345345          enddo   
     
    349349        do ifils=1,nqfils(iq)
    350350         iq2=iqfils(ifils,iq)
    351          call vlx_loc(Ratio,pente_max,masseq,u_mq,ijb_x,ije_x,iq2)
     351         call vlx_loc(Ratio,pente_max,masse,u_mq,ijb_x,ije_x,iq2)
    352352        enddo !do ifils=1,nqfils(iq)
    353353      endif !if (nqfils(iq).gt.0) then
     
    462462c$OMP THREADPRIVATE(airej2,airejjm)
    463463
    464       REAL masseq(ijb_u:ije_u,llm,nqtot),Ratio(ijb_u:ije_u,llm,nqtot) ! CRisi
     464      REAL Ratio(ijb_u:ije_u,llm,nqtot) ! CRisi
    465465      INTEGER ifils,iq2 ! CRisi
    466466c
     
    739739         DO l=1,llm
    740740         DO ij=ijb,ije
    741            masseq(ij,l,iq2)=masse(ij,l,iq)*q(ij,l,iq)
     741           masse(ij,l,iq2)=masse(ij,l,iq)*q(ij,l,iq)
    742742           Ratio(ij,l,iq2)=q(ij,l,iq2)/q(ij,l,iq)     
    743743          enddo   
     
    748748        do ifils=1,nqfils(iq)
    749749         iq2=iqfils(ifils,iq)
    750          call vly_loc(Ratio,pente_max,masseq,qbyv,iq2)
     750         call vly_loc(Ratio,pente_max,masse,qbyv,iq2)
    751751        enddo !do ifils=1,nqfils(iq)
    752752      endif !if (nqfils(iq).gt.0) then
     
    10171017         DO l=1,llm
    10181018          DO ij=ijb,ije
    1019            masseq(ij,l,iq2)=masse(ij,l,iq)*q(ij,l,iq)
     1019           masse(ij,l,iq2)=masse(ij,l,iq)*q(ij,l,iq)
    10201020           Ratio(ij,l,iq2)=q(ij,l,iq2)/q(ij,l,iq)
    1021            wq(ij,l,iq2)=wq(ij,l,iq)
     1021           !wq(ij,l,iq2)=wq(ij,l,iq) ! correction bug le 15mai2015
     1022           w(ij,l,iq2)=wq(ij,l,iq)
    10221023          enddo   
    10231024         enddo
     
    10251026        enddo !do ifils=1,nqdesc(iq)
    10261027c$OMP BARRIER
    1027        
     1028
    10281029        do ifils=1,nqfils(iq)
    10291030         iq2=iqfils(ifils,iq)
    1030          call vlz_loc(Ratio,pente_max,masseq,wq,ijb_x,ije_x,iq2)
     1031         call vlz_loc(Ratio,pente_max,masse,w,ijb_x,ije_x,iq2)
    10311032        enddo !do ifils=1,nqfils(iq)
    10321033      endif !if (nqfils(iq).gt.0) then
     
    10351036! CRisi: On rajoute ici une barrière car on veut être sur que tous les
    10361037! wq soient synchronisés
    1037       write(*,*) 'vlz 1032' 
     1038
    10381039c$OMP BARRIER
    10391040c$OMP DO SCHEDULE(STATIC,OMP_CHUNK)
     
    10491050c$OMP END DO NOWAIT
    10501051
     1052     
    10511053! retablir les fils en rapport de melange par rapport a l'air:
    10521054      if (nqfils(iq).gt.0) then 
     
    10621064        enddo !do ifils=1,nqdesc(iq)
    10631065      endif !if (nqfils(iq).gt.0) then
    1064 
    10651066
    10661067      RETURN
  • LMDZ5/trunk/libf/dyn3dmem/vlspltgen_loc.F

    r2270 r2281  
    193193
    194194      ! verif temporaire
    195       ijb=ij_begin-2*iip1
    196       ije=ij_end+2*iip1 
    197       if (pole_nord) ijb=ij_begin
    198       if (pole_sud)  ije=ij_end 
    199       if (ok_iso_verif) then
    200            call check_isotopes(zq,ijb,ije,'vlspltgen_loc 191')
     195      ijb=ij_begin
     196      ije=ij_end 
     197      if (ok_iso_verif) then
     198        call check_isotopes(zq,ijb,ije,'vlspltgen_loc 191')
    201199      endif !if (ok_iso_verif) then   
    202200
     
    459457c$OMP BARRIER       
    460458
    461           write(*,*) 'vlspltgen_loc 461'
    462459#ifdef _ADV_HALLO
    463           write(*,*) 'vlspltgen_loc 462'
    464460          call vlz_loc(zq,pente_max,zm,mw,
    465461     &               ij_begin+2*iip1,ij_end-2*iip1,iq)
     
    477473
    478474c$OMP BARRIER
     475      write(*,*) 'vlspltgen_loc 477'
    479476c$OMP MASTER
    480477      call VTb(VTHallo)
  • LMDZ5/trunk/libf/dyn3dmem/vlspltqs_loc.F

    r2270 r2281  
    3838      REAL adxqu(ijb_u:ije_u),dxqmax(ijb_u:ije_u,llm)
    3939      REAL u_mq(ijb_u:ije_u,llm)
    40       REAL masseq(ijb_u:ije_u,llm,nqtot),Ratio(ijb_u:ije_u,llm,nqtot) ! CRisi
     40      REAL Ratio(ijb_u:ije_u,llm,nqtot) ! CRisi
    4141      INTEGER ifils,iq2 ! CRisi
    4242
     
    345345         DO l=1,llm
    346346          DO ij=ijb,ije
    347            masseq(ij,l,iq2)=masse(ij,l,iq)*q(ij,l,iq)
     347           masse(ij,l,iq2)=masse(ij,l,iq)*q(ij,l,iq)
    348348           Ratio(ij,l,iq2)=q(ij,l,iq2)/q(ij,l,iq)     
    349349          enddo   
     
    354354         iq2=iqfils(ifils,iq)
    355355         write(*,*) 'vlxqs 349: on appelle vlx pour iq2=',iq2
    356          call vlx_loc(Ratio,pente_max,masseq,u_mq,ijb_x,ije_x,iq2)
     356         call vlx_loc(Ratio,pente_max,masse,u_mq,ijb_x,ije_x,iq2)
    357357        enddo !do ifils=1,nqfils(iq)
    358358      endif !if (nqfils(iq).gt.0) then
     
    462462c
    463463c
    464       REAL masseq(ijb_u:ije_u,llm,nqtot),Ratio(ijb_u:ije_u,llm,nqtot) ! CRisi
     464      REAL Ratio(ijb_u:ije_u,llm,nqtot) ! CRisi
    465465      INTEGER ifils,iq2 ! CRisi
    466466
     
    738738         DO l=1,llm
    739739          DO ij=ijb,ije
    740            masseq(ij,l,iq2)=masse(ij,l,iq)*q(ij,l,iq)
     740           masse(ij,l,iq2)=masse(ij,l,iq)*q(ij,l,iq)
    741741           Ratio(ij,l,iq2)=q(ij,l,iq2)/q(ij,l,iq)   
    742742          enddo   
     
    746746        do ifils=1,nqfils(iq)
    747747         iq2=iqfils(ifils,iq)
    748          call vly_loc(Ratio,pente_max,masseq,qbyv,iq2)
     748         call vly_loc(Ratio,pente_max,masse,qbyv,iq2)
    749749        enddo !do ifils=1,nqfils(iq)
    750750      endif !if (nqfils(iq).gt.0) then
  • LMDZ5/trunk/libf/dyn3dmem/vlz_mod.F90

    r2270 r2281  
    66  REAL,POINTER,SAVE :: adzqw(:,:)
    77  ! CRisi: pour les traceurs: 
    8   REAL,POINTER,SAVE :: masseq(:,:,:)
     8  !REAL,POINTER,SAVE :: masseq(:,:,:)
    99  REAL,POINTER,SAVE :: Ratio(:,:,:)
    1010 
     
    2626    CALL allocate_u(adzqw,llm,d)
    2727    if (nqdesc_tot.gt.0) then
    28     CALL allocate_u(masseq,llm,nqtot,d)
     28    !CALL allocate_u(masseq,llm,nqtot,d)
    2929    CALL allocate_u(Ratio,llm,nqtot,d)
    3030    endif !if (nqdesc_tot.gt.0) then
     
    4646    ! CRisi:
    4747    if (nqdesc_tot.gt.0) then   
    48     CALL switch_u(masseq,distrib_vanleer,dist)
     48    !CALL switch_u(masseq,distrib_vanleer,dist)
    4949    CALL switch_u(Ratio,distrib_vanleer,dist)
    5050    endif !if (nqdesc_tot.gt.0) then     
Note: See TracChangeset for help on using the changeset viewer.