Changeset 1344 for LMDZ4/trunk


Ignore:
Timestamp:
Apr 9, 2010, 10:00:14 AM (14 years ago)
Author:
Ehouarn Millour
Message:

Minor fix: Tabs at the beginning of lines are not standard (and differently interpreted by compilers; in the present case gfortran failed to compile) and have been replaced by blanks.

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ4/trunk/libf/phylmd/isccp_cloud_types.F

    r1146 r1344  
    11!
    2 ! $Header$
     2! $Id $
    33!
    44      SUBROUTINE ISCCP_CLOUD_TYPES(
     
    3131     &     boxptop
    3232     &)
    33        
     33       
    3434
    3535! Copyright Steve Klein and Mark Webb 2002 - all rights reserved.
     
    6767c                                       !  to a different value for each model
    6868c                                       !  gridbox it is called on, as it is
    69 c                                       !  possible that the choice of the samec
    70 c                                       !  seed value every time may introduce some
    71 c                                       !  statistical bias in the results, particularly
    72 c                                       !  for low values of NCOL.
     69c                                          !  possible that the choice of the samec
     70c                                        !  seed value every time may introduce some
     71c                                        !  statistical bias in the results, particularly
     72c                                        !  for low values of NCOL.
    7373c
    74       REAL pfull(npoints,nlev)          !  pressure of full model levels (Pascals)
     74      REAL pfull(npoints,nlev)                      !  pressure of full model levels (Pascals)
    7575c                                        !  pfull(npoints,1)    is    top level of model
    7676c                                        !  pfull(npoints,nlev) is bottom level of model
     
    9292
    9393      REAL dtau_s(npoints,nlev)         !  mean 0.67 micron optical depth of stratiform
    94 c                                       !  clouds in each model level
     94c                                        !  clouds in each model level
    9595c                                        !  NOTE:  this the cloud optical depth of only the
    9696c                                        !         cloudy part of the grid box, it is not weighted
     
    9999
    100100      REAL dtau_c(npoints,nlev)         !  mean 0.67 micron optical depth of convective
    101 c                                       !  clouds in each
     101c                                        !  clouds in each
    102102c                                        !  model level.  Same note applies as in dtau_s.
    103103
    104104      INTEGER overlap                   !  overlap type
    105                                        
     105                                       
    106106!  1=max
    107                                        
     107                                       
    108108!  2=rand
    109109!  3=max/rand
     
    111111      INTEGER top_height                !  1 = adjust top height using both a computed
    112112c                                        !  infrared brightness temperature and the visible
    113 c                                       !  optical depth to adjust cloud top pressure. Note
    114 c                                       !  that this calculation is most appropriate to compare
    115 c                                       !  to ISCCP data during sunlit hours.
     113c                                        !  optical depth to adjust cloud top pressure. Note
     114c                                        !  that this calculation is most appropriate to compare
     115c                                        !  to ISCCP data during sunlit hours.
    116116c                                        !  2 = do not adjust top height, that is cloud top
    117117c                                        !  pressure is the actual cloud top pressure
    118118c                                        !  in the model
    119 c                                       !  3 = adjust top height using only the computed
    120 c                                       !  infrared brightness temperature. Note that this
    121 c                                       !  calculation is most appropriate to compare to ISCCP
    122 c                                       !  IR only algortihm (i.e. you can compare to nighttime
    123 c                                       !  ISCCP data with this option)
     119c                                        !  3 = adjust top height using only the computed
     120c                                        !  infrared brightness temperature. Note that this
     121c                                        !  calculation is most appropriate to compare to ISCCP
     122c                                        !  IR only algortihm (i.e. you can compare to nighttime
     123c                                        !  ISCCP data with this option)
    124124
    125125      REAL tautab(0:255)                !  ISCCP table for converting count value to
     
    135135      REAL at(npoints,nlev)                   !  temperature in each model level (K)
    136136      REAL dem_s(npoints,nlev)                !  10.5 micron longwave emissivity of stratiform
    137 c                                       !  clouds in each
     137c                                        !  clouds in each
    138138c                                        !  model level.  Same note applies as in dtau_s.
    139139      REAL dem_c(npoints,nlev)                  !  10.5 micron longwave emissivity of convective
    140 c                                       !  clouds in each
     140c                                        !  clouds in each
    141141c                                        !  model level.  Same note applies as in dtau_s.
    142142cIM reg.dyn BEG
     
    161161      REAL totalcldarea(npoints)        !  the fraction of model grid box columns
    162162c                                        !  with cloud somewhere in them.  This should
    163 c                                       !  equal the sum over all entries of fq_isccp
    164        
    165        
     163c                                        !  equal the sum over all entries of fq_isccp
     164       
     165       
    166166c      ! The following three means are averages over the cloudy areas only.  If no
    167 c      ! clouds are in grid box all three quantities should equal zero. 
    168                                        
     167c      ! clouds are in grid box all three quantities should equal zero.       
     168                                       
    169169      REAL meanptop(npoints)            !  mean cloud top pressure (mb) - linear averaging
    170170c                                        !  in cloud top pressure.
    171                                        
     171                                       
    172172      REAL meantaucld(npoints)          !  mean optical thickness
    173173c                                        !  linear averaging in albedo performed.
     
    176176     
    177177      REAL boxptop(npoints,ncol)        !  cloud top pressure (mb) in each column
    178                                        
    179                                                                                                                        
     178                                       
     179                                                                                                                       
    180180!
    181181!     ------
     
    184184
    185185      REAL frac_out(npoints,ncol,nlev) ! boxes gridbox divided up into
    186 c                                       ! Equivalent of BOX in original version, but
    187 c                                       ! indexed by column then row, rather than
    188 c                                       ! by row then column
     186c                                        ! Equivalent of BOX in original version, but
     187c                                        ! indexed by column then row, rather than
     188c                                        ! by row then column
    189189
    190190      REAL tca(npoints,0:nlev) ! total cloud cover in each model level (fraction)
     
    205205
    206206      REAL dem(npoints,ncol),bb(npoints)     !  working variables for 10.5 micron longwave
    207 c                                       !  emissivity in part of
    208 c                                       !  gridbox under consideration
    209 
    210       REAL ran(npoints)                 ! vector of random numbers
     207c                                        !  emissivity in part of
     208c                                        !  gridbox under consideration
     209
     210      REAL ran(npoints)                   ! vector of random numbers
    211211      REAL ptrop(npoints)
    212212      REAL attrop(npoints)
     
    248248      real boxarea
    249249      integer debug       ! set to non-zero value to print out inputs
    250 c                         ! with step debug
     250c                          ! with step debug
    251251      integer debugcol    ! set to non-zero value to print out column
    252 c                         ! decomposition with step debugcol
     252c                          ! decomposition with step debugcol
    253253
    254254      integer index1(npoints),num1,jj
     
    293293c          write(6,'(a10)') 'invtau(1:100)='
    294294c          write(6,'(8i10)') (invtau(i),i=1,100)
    295 c         do j=1,npoints,debug
     295c          do j=1,npoints,debug
    296296c          write(6,'(a10)') 'j='
    297297c          write(6,'(8I10)') j
     
    322322c          write(6,'(a10)') 'dem_c='
    323323c          write(6,'(8f10.2)') (dem_c(j,i),i=1,nlev)
    324 c         enddo
     324c          enddo
    325325c      endif
    326326
     
    361361cIM
    362362c      if (ncolprint.ne.0) then
    363 c       do j=1,npoints,1000
     363c        do j=1,npoints,1000
    364364c        write(6,'(a10)') 'j='
    365365c        write(6,'(8I10)') j
     
    375375c        write (6,'(8f5.2)')
    376376c     &   ((cca(j,ilev),ibox=1,ncolprint),ilev=1,nlev)
    377 c       enddo
     377c        enddo
    378378c      endif
    379379
     
    415415c       do j=1,npoints
    416416c           if (cc(j,ilev) .lt. 0. .or. cc(j,ilev) .gt. 1.) then
    417 c       num1=num1+1
    418 c       index1(num1)=j
     417c        num1=num1+1
     418c        index1(num1)=j
    419419c           end if
    420420c       enddo
    421421c       do jj=1,num1   
    422 c       j=index1(jj)
     422c        j=index1(jj)
    423423c               write(6,*)  ' error = cloud fraction less than zero'
    424 c       write(6,*) ' or '
     424c        write(6,*) ' or '
    425425c               write(6,*)  ' error = cloud fraction greater than 1'
    426 c       write(6,*) 'value at point ',j,' is ',cc(j,ilev)
    427 c       write(6,*) 'level ',ilev
     426c        write(6,*) 'value at point ',j,' is ',cc(j,ilev)
     427c        write(6,*) 'level ',ilev
    428428c               STOP
    429429c       enddo
     
    431431c       do j=1,npoints
    432432c           if (conv(j,ilev) .lt. 0. .or. conv(j,ilev) .gt. 1.) then
    433 c       num1=num1+1
    434 c       index1(num1)=j
     433c        num1=num1+1
     434c        index1(num1)=j
    435435c           end if
    436436c       enddo
    437437c       do jj=1,num1   
    438 c       j=index1(jj)
     438c        j=index1(jj)
    439439c               write(6,*) 
    440440c    &           ' error = convective cloud fraction less than zero'
    441 c       write(6,*) ' or '
     441c        write(6,*) ' or '
    442442c               write(6,*) 
    443443c    &           ' error = convective cloud fraction greater than 1'
    444 c       write(6,*) 'value at point ',j,' is ',conv(j,ilev)
    445 c       write(6,*) 'level ',ilev
     444c        write(6,*) 'value at point ',j,' is ',conv(j,ilev)
     445c        write(6,*) 'level ',ilev
    446446c               STOP
    447447c       enddo
     
    450450c       do j=1,npoints
    451451c           if (dtau_s(j,ilev) .lt. 0.) then
    452 c       num1=num1+1
    453 c       index1(num1)=j
     452c        num1=num1+1
     453c        index1(num1)=j
    454454c           end if
    455455c       enddo
    456456c       do jj=1,num1   
    457 c       j=index1(jj)
     457c        j=index1(jj)
    458458c               write(6,*) 
    459459c    &           ' error = stratiform cloud opt. depth less than zero'
    460 c       write(6,*) 'value at point ',j,' is ',dtau_s(j,ilev)
    461 c       write(6,*) 'level ',ilev
     460c        write(6,*) 'value at point ',j,' is ',dtau_s(j,ilev)
     461c        write(6,*) 'level ',ilev
    462462c               STOP
    463463c       enddo
     
    465465c       do j=1,npoints
    466466c           if (dtau_c(j,ilev) .lt. 0.) then
    467 c       num1=num1+1
    468 c       index1(num1)=j
     467c        num1=num1+1
     468c        index1(num1)=j
    469469c           end if
    470470c       enddo
    471471c       do jj=1,num1   
    472 c       j=index1(jj)
     472c        j=index1(jj)
    473473c               write(6,*) 
    474474c    &           ' error = convective cloud opt. depth less than zero'
    475 c       write(6,*) 'value at point ',j,' is ',dtau_c(j,ilev)
    476 c       write(6,*) 'level ',ilev
     475c        write(6,*) 'value at point ',j,' is ',dtau_c(j,ilev)
     476c        write(6,*) 'level ',ilev
    477477c               STOP
    478478c       enddo
     
    481481c       do j=1,npoints
    482482c           if (dem_s(j,ilev) .lt. 0. .or. dem_s(j,ilev) .gt. 1.) then
    483 c       num1=num1+1
    484 c       index1(num1)=j
     483c        num1=num1+1
     484c        index1(num1)=j
    485485c           end if
    486486c       enddo
    487487c       do jj=1,num1   
    488 c       j=index1(jj)
     488c        j=index1(jj)
    489489c               write(6,*) 
    490490c    &           ' error = stratiform cloud emissivity less than zero'
    491 c       write(6,*)'or'
     491c        write(6,*)'or'
    492492c               write(6,*) 
    493493c    &           ' error = stratiform cloud emissivity greater than 1'
    494 c       write(6,*) 'value at point ',j,' is ',dem_s(j,ilev)
    495 c       write(6,*) 'level ',ilev
     494c        write(6,*) 'value at point ',j,' is ',dem_s(j,ilev)
     495c        write(6,*) 'level ',ilev
    496496c               STOP
    497497c       enddo
     
    500500c       do j=1,npoints
    501501c           if (dem_c(j,ilev) .lt. 0. .or. dem_c(j,ilev) .gt. 1.) then
    502 c       num1=num1+1
    503 c       index1(num1)=j
     502c        num1=num1+1
     503c        index1(num1)=j
    504504c           end if
    505505c       enddo
    506506c       do jj=1,num1   
    507 c       j=index1(jj)
     507c        j=index1(jj)
    508508c               write(6,*) 
    509509c    &           ' error = convective cloud emissivity less than zero'
    510 c       write(6,*)'or'
     510c        write(6,*)'or'
    511511c               write(6,*) 
    512512c    &           ' error = convective cloud emissivity greater than 1'
     
    520520      do ibox=1,ncol
    521521        do j=1,npoints
    522           boxpos(j,ibox)=(ibox-.5)/ncol
     522          boxpos(j,ibox)=(ibox-.5)/ncol
    523523        enddo
    524524      enddo
     
    533533        do ibox=1,ncol
    534534          do j=1,npoints
    535             frac_out(j,ibox,ilev)=0.0
     535            frac_out(j,ibox,ilev)=0.0
    536536          enddo
    537537        enddo
     
    572572
    573573        IF (ilev.eq.1) then
    574             ! If max overlap
    575             IF (overlap.eq.1) then
    576               ! select pixels spread evenly
    577               ! across the gridbox
     574            ! If max overlap
     575            IF (overlap.eq.1) then
     576              ! select pixels spread evenly
     577              ! across the gridbox
    578578              DO ibox=1,ncol
    579579                do j=1,npoints
     
    581581                enddo
    582582              enddo
    583             ELSE
     583            ELSE
    584584              DO ibox=1,ncol
    585585                call ran0_vec(npoints,seed,ran)
    586                 ! select random pixels from the non-convective
    587                 ! part the gridbox ( some will be converted into
    588                 ! convective pixels below )
     586                ! select random pixels from the non-convective
     587                ! part the gridbox ( some will be converted into
     588                ! convective pixels below )
    589589                do j=1,npoints
    590590                  threshold(j,ibox)=
     
    659659          ! Reset threshold
    660660          call ran0_vec(npoints,seed,ran)
    661            
     661           
    662662          do j=1,npoints
    663663            threshold(j,ibox)=
     
    698698           ENDDO
    699699
    700 !          Code to partition boxes into startiform and convective parts
    701 !          goes here
     700!           Code to partition boxes into startiform and convective parts
     701!           goes here
    702702
    703703           DO ibox=1,ncol
     
    744744c            write (6,'(8f5.2)')
    745745c     &       ((frac_out(j,ibox,ilev2),ibox=1,ncolprint),ilev2=1,nlev)
    746 c           enddo
     746c            enddo
    747747c          endif
    748748
     
    762762        do j=1,npoints
    763763            tau(j,ibox)=0.
    764             albedocld(j,ibox)=0.
    765             boxtau(j,ibox)=0.
    766             boxptop(j,ibox)=0.
    767             box_cloudy(j,ibox)=.false.
     764            albedocld(j,ibox)=0.
     765            boxtau(j,ibox)=0.
     766            boxptop(j,ibox)=0.
     767            box_cloudy(j,ibox)=.false.
    768768        enddo
    76976915    continue
     
    865865c     &           tauwv(j),dem_wv(j,ilev)
    866866c               enddo
    867 c              endif
     867c               endif
    868868125     continue
    869869
     
    879879            ! Black body emission at temperature of the layer
    880880
    881                 bb(j)=1 / ( exp(1307.27/at(j,ilev)) - 1. )
    882                 !bb(j)= 5.67e-8*at(j,ilev)**4
    883 
    884                 ! increase TOA flux by flux emitted from layer
    885                 ! times total transmittance in layers above
     881                bb(j)=1 / ( exp(1307.27/at(j,ilev)) - 1. )
     882                !bb(j)= 5.67e-8*at(j,ilev)**4
     883
     884                ! increase TOA flux by flux emitted from layer
     885                ! times total transmittance in layers above
    886886
    887887                fluxtop_clrsky(j) = fluxtop_clrsky(j)
     
    889889           
    890890                ! update trans_layers_above with transmissivity
    891                 ! from this layer for next time around loop
     891                ! from this layer for next time around loop
    892892
    893893                trans_layers_above_clrsky(j)=
     
    935935c     &       trans_layers_above_clrsky(j)
    936936c        enddo
    937 c       endif
     937c        endif
    938938   
    939939
     
    971971                ! Black body emission at temperature of the layer
    972972
    973                 bb(j)=1 / ( exp(1307.27/at(j,ilev)) - 1. )
    974                 !bb(j)= 5.67e-8*at(j,ilev)**4
     973                bb(j)=1 / ( exp(1307.27/at(j,ilev)) - 1. )
     974                !bb(j)= 5.67e-8*at(j,ilev)**4
    975975              enddo
    976976
     
    978978              do j=1,npoints
    979979
    980                 ! emissivity for point in this layer
     980                ! emissivity for point in this layer
    981981cIM REAL             if (frac_out(j,ibox,ilev).eq.1) then
    982982                if (frac_out(j,ibox,ilev).eq.1.0) then
     
    993993
    994994                ! increase TOA flux by flux emitted from layer
    995                 ! times total transmittance in layers above
     995                ! times total transmittance in layers above
    996996
    997997                fluxtop(j,ibox) = fluxtop(j,ibox)
     
    10001000           
    10011001                ! update trans_layers_above with transmissivity
    1002                 ! from this layer for next time around loop
     1002                ! from this layer for next time around loop
    10031003
    10041004                trans_layers_above(j,ibox)=
     
    10291029c              write (6,'(8f7.2)')
    10301030c     &          (trans_layers_above(j,ibox),ibox=1,ncolprint)
    1031 c             enddo
     1031c              enddo
    10321032c          endif
    10331033
     
    10711071c          write (6,'(8f7.2)') (100.*fluxtop(j,ibox),ibox=1,ncolprint)
    10721072c          end do
    1073 c       endif
     1073c        endif
    10741074   
    10751075        !now that you have the top of atmosphere radiance account
     
    10821082        !adjustment performed in this section
    10831083        !
    1084         !If it turns out that the cloud brightness temperature
    1085         !is greater than 260K, then the liquid cloud conversion
     1084        !If it turns out that the cloud brightness temperature
     1085        !is greater than 260K, then the liquid cloud conversion
    10861086        !factor of 2.56 is used.
    1087         !
     1087        !
    10881088        !Note that this is discussed on pages 85-87 of
    10891089        !the ISCCP D level documentation (Rossow et al. 1996)
     
    10971097            transmax(j) = (fluxtop(j,ibox)-btcmin(j))
    10981098     &                /(fluxtop_clrsky(j)-btcmin(j))
    1099             !note that the initial setting of tauir(j) is needed so that
    1100             !tauir(j) has a realistic value should the next if block be
    1101             !bypassed
     1099            !note that the initial setting of tauir(j) is needed so that
     1100            !tauir(j) has a realistic value should the next if block be
     1101            !bypassed
    11021102            tauir(j) = tau(j,ibox) * rec2p13
    11031103            taumin(j) = -1. * log(max(min(transmax(j),0.9999999),0.001))
     
    11101110     &          transmax(j) .le. 0.9999999) then
    11111111                fluxtopinit(j) = fluxtop(j,ibox)
    1112                 tauir(j) = tau(j,ibox) *rec2p13
     1112                tauir(j) = tau(j,ibox) *rec2p13
    11131113              endif
    11141114            enddo
     
    11261126     &              / (log(1. + (1./fluxtop(j,ibox))))
    11271127                  if (tb(j,ibox) .gt. 260.) then
    1128                     tauir(j) = tau(j,ibox) / 2.56
    1129                   end if                       
     1128                    tauir(j) = tau(j,ibox) / 2.56
     1129                  end if                       
    11301130                end if
    11311131                end if
     
    11411141                if (top_height.eq.1.and.tauir(j).lt.taumin(j)) then
    11421142                         tb(j,ibox) = attrop(j) - 5.
    1143                         tau(j,ibox) = 2.13*taumin(j)
     1143                        tau(j,ibox) = 2.13*taumin(j)
    11441144                end if
    11451145            else
     
    11811181c          write (6,'(a)') 'total_trans:'
    11821182c          write (6,'(8f7.2)')
    1183 c     &   (trans_layers_above(j,ibox),ibox=1,ncolprint)
     1183c     &          (trans_layers_above(j,ibox),ibox=1,ncolprint)
    11841184   
    11851185c          write (6,'(a)') 'total_emiss:'
    11861186c          write (6,'(8f7.2)')
    1187 c     &   (1.0-trans_layers_above(j,ibox),ibox=1,ncolprint)
     1187c     &          (1.0-trans_layers_above(j,ibox),ibox=1,ncolprint)
    11881188   
    11891189c          write (6,'(a)') 'total_trans:'
    11901190c          write (6,'(8f7.2)')
    1191 c     &   (trans_layers_above(j,ibox),ibox=1,ncolprint)
     1191c     &          (trans_layers_above(j,ibox),ibox=1,ncolprint)
    11921192   
    11931193c          write (6,'(a)') 'ppout:'
    11941194c          write (6,'(8f7.2)') (tb(j,ibox),ibox=1,ncolprint)
    11951195c          enddo ! j
    1196 c       endif
     1196c        endif
    11971197
    11981198      end if
     
    12641264     &           .and.(frac_out(j,ibox,ilev) .ne. 0.0)) then
    12651265                ptop(j,ibox)=pfull(j,ilev)
    1266                 levmatch(j,ibox)=ilev
     1266                levmatch(j,ibox)=ilev
    12671267              end if
    12681268            end do
     
    13571357
    13581358                !convert optical thickness to albedo
    1359                 albedocld(j,ibox)
     1359                  albedocld(j,ibox)
    13601360     &            =real(invtau(min(nint(100.*tau(j,ibox)),45000)))
    1361            
     1361           
    13621362                !contribute to averaging
    1363                 meanalbedocld(j) = meanalbedocld(j)
     1363                meanalbedocld(j) = meanalbedocld(j)
    13641364     &            +albedocld(j,ibox)*boxarea
    13651365
     
    14411441   
    14421442            if (box_cloudy(j,ibox)) then
    1443            
     1443           
    14441444              meanptop(j) = meanptop(j) + ptop(j,ibox)*boxarea
    14451445
     
    15561556      !compute mean cloud properties
    15571557      do j=1,npoints
    1558         if (totalcldarea(j) .gt. 0.) then
    1559           meanptop(j) = meanptop(j) / totalcldarea(j)
    1560           if (sunlit(j).eq.1) then
    1561             meanalbedocld(j) = meanalbedocld(j) / totalcldarea(j)
    1562             meantaucld(j) = tautab(min(255,max(1,nint(meanalbedocld(j)))))
    1563           end if
    1564         end if
     1558       if (totalcldarea(j) .gt. 0.) then
     1559         meanptop(j) = meanptop(j) / totalcldarea(j)
     1560         if (sunlit(j).eq.1) then
     1561           meanalbedocld(j)=meanalbedocld(j) / totalcldarea(j)
     1562           meantaucld(j)=tautab(min(255,max(1,nint(meanalbedocld(j)))))
     1563         end if
     1564       end if
    15651565      enddo ! j
    15661566!
     
    16501650                                     
    16511651c               write (6,'(8I7)') (ibox,ibox=1,ncolprint)
    1652              
     1652             
    16531653c               write (6,'(a)') 'tau:'
    16541654c               write (6,'(8f7.2)') (tau(j,ibox),ibox=1,ncolprint)
Note: See TracChangeset for help on using the changeset viewer.