Ignore:
Timestamp:
Aug 3, 2024, 2:56:58 PM (5 months ago)
Author:
abarral
Message:

Put .h into modules

Location:
LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm
Files:
33 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/gppref.F90

    r5159 r5160  
    134134IF (LVERTFE) THEN
    135135  DO JLEV=1,KFLEV
    136 !   print *,'GPPREF: LVERTFE KFLEV KSTART KPROF JLEV',LVERTFE,KFLEV,KSTART,KPROF,JLEV
     136!   PRINT *,'GPPREF: LVERTFE KFLEV KSTART KPROF JLEV',LVERTFE,KFLEV,KSTART,KPROF,JLEV
    137137    PRESF(KSTART:KPROF,JLEV)=VAF(JLEV)+VBF(JLEV)*PRESH(KSTART:KPROF,KFLEV) 
    138138  ENDDO
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/gpxyb.F90

    r1990 r5160  
    121121! The first block if is for economy (no do loop start up) and the second
    122122! for safety.
    123 !print *,'GPXYB: NDLNPR RHYDR0=',NDLNPR,RHYDR0
     123!PRINT *,'GPXYB: NDLNPR RHYDR0=',NDLNPR,RHYDR0
    124124TOPPRES=0.1  !!!!! A REVOIR (MPL) 29042010 passe de 0 a 0.1 comme ARPEGE
    125125IF(PRES(KSTART,0) <= TOPPRES)THEN
     
    139139!              --------------------
    140140
    141 !print *,'NDLNPR LVERTFE',NDLNPR,LVERTFE
     141!PRINT *,'NDLNPR LVERTFE',NDLNPR,LVERTFE
    142142IF(NDLNPR == 0) THEN
    143143
     
    177177         & *(PVDELB(JLEV)+PVC(JLEV)*PLNPR(JLON,JLEV)*PRDELP(JLON,&
    178178         & JLEV)) 
    179 !       print *,'GPXYB JLEV JLON JJ PRES ZPRES PDELP ', JLEV,JLON,JJ,PRES(JLON,JLEV),ZRPRES(JLON,JJ),PDELP(JLON,JLEV)
    180 !       print *,'GPXYB JLEV JLON JM PRDELP PLNPR ', JLEV,JLON,JM,PRDELP(JLON,JLEV),PLNPR (JLON,JLEV)
    181 !       print *,'GPXYB JLEV JLON JJ PRPRES PALPH ', JLEV,JLON,JJ,PRPRES(JLON,JLEV),PALPH (JLON,JLEV)
    182 !       print *,'GPXYB JLEV JLON PRPP PRTGR PVDELB PVC ', JLEV,JLON,PRPP  (JLON,JLEV),PRTGR (JLON,JLEV),PVDELB(JLEV),PVC(JLEV)
     179!       PRINT *,'GPXYB JLEV JLON JJ PRES ZPRES PDELP ', JLEV,JLON,JJ,PRES(JLON,JLEV),ZRPRES(JLON,JJ),PDELP(JLON,JLEV)
     180!       PRINT *,'GPXYB JLEV JLON JM PRDELP PLNPR ', JLEV,JLON,JM,PRDELP(JLON,JLEV),PLNPR (JLON,JLEV)
     181!       PRINT *,'GPXYB JLEV JLON JJ PRPRES PALPH ', JLEV,JLON,JJ,PRPRES(JLON,JLEV),PALPH (JLON,JLEV)
     182!       PRINT *,'GPXYB JLEV JLON PRPP PRTGR PVDELB PVC ', JLEV,JLON,PRPP  (JLON,JLEV),PRTGR (JLON,JLEV),PVDELB(JLEV),PVC(JLEV)
    183183      ENDDO
    184184      JTEMP=JM
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/lw.F90

    r5158 r5160  
    142142
    143143IF (LHOOK) CALL DR_HOOK('LW',0,ZHOOK_HANDLE)
    144 print *,'    LW: Avant LWU'
     144PRINT *,'    LW: Avant LWU'
    145145CALL LWU &
    146146 & (  KIDIA, KFDIA, KLON, KLEV,&
     
    156156!                ---------------------------------
    157157
    158 print *,'    LW: Avant LWBV'
     158PRINT *,'    LW: Avant LWBV'
    159159CALL LWBV &
    160160 & ( KIDIA, KFDIA, KLON , KLEV  , KMODE,&
     
    169169!                --------------------------------
    170170
    171 print *,'    LW: Avant LWC'
     171PRINT *,'    LW: Avant LWC'
    172172CALL LWC &
    173173 & ( KIDIA , KFDIA, KLON  , KLEV,&
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/lwb.F90

    r1990 r5160  
    115115!                  ------------------------------
    116116
    117 print *,'dans LWB'
     117PRINT *,'dans LWB'
    118118IF (LHOOK) CALL DR_HOOK('LWB',0,ZHOOK_HANDLE)
    119119ILEV2=2*KLEV
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/lwbv.F90

    r1990 r5160  
    123123
    124124IF (LHOOK) CALL DR_HOOK('LWBV',0,ZHOOK_HANDLE)
    125 print *,'LWBV: avant LWB'
     125PRINT *,'LWBV: avant LWB'
    126126CALL LWB &
    127127 & ( KIDIA, KFDIA, KLON  , KLEV  , KMODE,&
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/lwc.F90

    r1990 r5160  
    114114!100  CONTINUE
    115115
    116 !      print *,' Enter LWC '
     116!      PRINT *,' Enter LWC '
    117117IF (LHOOK) CALL DR_HOOK('LWC',0,ZHOOK_HANDLE)
    118118DO JL = KIDIA,KFDIA
     
    152152  ENDDO
    153153ENDDO
    154 !      print *,' LWC after Initialisation to clear-sky fluxes'
     154!      PRINT *,' LWC after Initialisation to clear-sky fluxes'
    155155
    156156!*         2.1     FLUXES FOR ONE OVERCAST UNITY EMISSIVITY CLOUD
     
    211211
    212212ENDDO
    213 !      print *,' LWC after 213: Fluxes for unity emissivity'
     213!      PRINT *,' LWC after 213: Fluxes for unity emissivity'
    214214
    215215!*         2.2     CLOUD COVER MATRIX
     
    228228  ENDDO
    229229ENDDO
    230 !      print *,' LWC after Initialisation CC matrix'
     230!      PRINT *,' LWC after Initialisation CC matrix'
    231231
    232232!*         2.4     CLOUD COVER BELOW THE LEVEL OF CALCULATION
     
    279279
    280280ENDDO
    281 !      print *,' LWC after 244: CC below level of calculation'
     281!      PRINT *,' LWC after 244: CC below level of calculation'
    282282
    283283!*         2.5     CLOUD COVER ABOVE THE LEVEL OF CALCULATION
     
    329329  ENDDO
    330330ENDDO
    331 !      print *,' LWC after 254: CC above level of calculation'
     331!      PRINT *,' LWC after 254: CC above level of calculation'
    332332
    333333!*         3.      FLUXES FOR PARTIAL/MULTIPLE LAYERED CLOUDINESS
     
    371371
    372372ENDDO
    373 !      print *,' LWC after 317: Downward fluxes'
     373!      PRINT *,' LWC after 317: Downward fluxes'
    374374
    375375!*         3.2     UPWARD FLUX AT THE SURFACE
     
    413413
    414414ENDDO
    415 !      print *,' LWC after 337: Upward fluxes'
     415!      PRINT *,' LWC after 337: Upward fluxes'
    416416
    417417!-----------------------------------------------------------------------
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/lwu.F90

    r5159 r5160  
    223223    IAE2 = 3 * KLEV + 1 - (IJ + 1)
    224224    IAE3 = 3 * KLEV + 1 - IJPN
    225     ! print *,'IAE1= ',IAE1
    226     ! print *,'IAE2= ',IAE2
    227     ! print *,'IAE3= ',IAE3
    228     ! print *,'KIDIA= ',KIDIA
    229     ! print *,'KFDIA= ',KFDIA
    230     ! print *,'KLEV= ',KLEV
     225    ! PRINT *,'IAE1= ',IAE1
     226    ! PRINT *,'IAE2= ',IAE2
     227    ! PRINT *,'IAE3= ',IAE3
     228    ! PRINT *,'KIDIA= ',KIDIA
     229    ! PRINT *,'KFDIA= ',KFDIA
     230    ! PRINT *,'KLEV= ',KLEV
    231231    DO JAE = 1, 6
    232232      DO JL = KIDIA, KFDIA
    233         !   print *,'JL= ',JL,'-JAE= ',JAE,'-JK= ',JK,'-NSIL= ',NSIL
     233        !   PRINT *,'JL= ',JL,'-JAE= ',JAE,'-JK= ',JK,'-NSIL= ',NSIL
    234234        ZUAER(JL, JAE) = &
    235235                & (RAER(JAE, 1) * PAER(JL, 1, JK) + RAER(JAE, 2) * PAER(JL, 2, JK)&
     
    363363
    364364  ENDDO
    365   !      print *,'END OF LWU'
     365  !      PRINT *,'END OF LWU'
    366366
    367367
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/posnam.F90

    r1990 r5160  
    7171ISTATUS=0
    7272ISCAN=0
    73 print *,'On cherche a lire:',CDNAML
     73PRINT *,'On cherche a lire:',CDNAML
    7474DO WHILE (ISTATUS==0 .AND. ISCAN==0)
    7575  READ(KULNAM,'(A)',IOSTAT=ISTATUS) CLINE
    76 ! print *,'CLINE,ISTATUS= ',CLINE,ISTATUS
     76! PRINT *,'CLINE,ISTATUS= ',CLINE,ISTATUS
    7777  SELECT CASE (ISTATUS)
    7878  CASE (:-1)
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/radlsw.F90

    r5159 r5160  
    10641064!                 ------------------------------------
    10651065
    1066 !print *,'RADLSW: LPHYLIN, LRRTM',LPHYLIN, LRRTM
     1066!PRINT *,'RADLSW: LPHYLIN, LRRTM',LPHYLIN, LRRTM
    10671067IF (.NOT.LPHYLIN) THEN
    10681068  IF ( .NOT. LRRTM) THEN
     
    10761076     & ZEMIT , PFLUX , PFLUC &
    10771077     & ) 
    1078 !   print *,'RADLSW: apres CALL LW'
     1078!   PRINT *,'RADLSW: apres CALL LW'
    10791079    IF(LLDEBUG) THEN
    10801080    call writefield_phy('radlsw_flux1',PFLUX(:,1,:),klev+1)
     
    11031103    ENDDO
    11041104
    1105 !   print *,'RADLSW: avant CALL RRTM_RRTM_140GP,PAP=',PAP(1,:)
     1105!   PRINT *,'RADLSW: avant CALL RRTM_RRTM_140GP,PAP=',PAP(1,:)
    11061106    CALL RRTM_RRTM_140GP &
    11071107     & ( KIDIA , KFDIA , KLON  , KLEV,&
     
    11131113     & PTAU_LW,&
    11141114     & ZEMIT , PFLUX , PFLUC , ZTCLEAR )
    1115 !   print *,'RADLSW: apres CALL RRTM_RRTM_140GP'
     1115!   PRINT *,'RADLSW: apres CALL RRTM_RRTM_140GP'
    11161116
    11171117  ENDIF
     
    11201120  PFLUX(:,:,:)= 0.0_JPRB
    11211121  PFLUC(:,:,:)= 0.0_JPRB
    1122 ! print *,'RADLSW: ZEMIT,PFLUX et PFLUC = 0'
     1122! PRINT *,'RADLSW: ZEMIT,PFLUX et PFLUC = 0'
    11231123ENDIF
    11241124
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/read_rsun_rrtm.F90

    r5159 r5160  
    102102      solaire=TSI(days_elapsed+1)
    103103
    104       print *,'READ_RSUN_RRTM day=', days_elapsed+1,' solaire=', solaire, ' RSUN=', RSUN(1:NSW)
     104      PRINT *,'READ_RSUN_RRTM day=', days_elapsed+1,' solaire=', solaire, ' RSUN=', RSUN(1:NSW)
    105105
    106106    ENDIF !--fin allocation
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/readaerosolstrato1_rrtm.F90

    r5159 r5160  
    8585
    8686    IF (nbands_sw_rrtm.NE.6) THEN
    87         print *,'nbands_sw_rrtm doit etre egal a 6 dans readaerosolstrat_rrtm'
     87        PRINT *,'nbands_sw_rrtm doit etre egal a 6 dans readaerosolstrat_rrtm'
    8888        STOP
    8989    ENDIF
     
    9595    n_lev = size(lev)
    9696    IF (n_lev.NE.klev) THEN
    97        print *,'Le nombre de niveaux n est pas egal a klev'
     97       PRINT *,'Le nombre de niveaux n est pas egal a klev'
    9898       STOP
    9999    ENDIF
     
    102102    CALL nf95_gw_var(ncid_in, varid, latitude)
    103103    n_lat = size(latitude)
    104     print *, 'LAT aerosol strato=', n_lat, latitude
     104    PRINT *, 'LAT aerosol strato=', n_lat, latitude
    105105
    106106    IF (grid_type/=unstructured) THEN
    107107      IF (n_lat.NE.nbp_lat) THEN
    108          print *,'Le nombre de lat n est pas egal a nbp_lat'
     108         PRINT *,'Le nombre de lat n est pas egal a nbp_lat'
    109109         STOP
    110110      ENDIF
     
    114114    CALL nf95_gw_var(ncid_in, varid, longitude)
    115115    n_lon = size(longitude)
    116     print *, 'LON aerosol strato=', n_lon, longitude
     116    PRINT *, 'LON aerosol strato=', n_lon, longitude
    117117
    118118    IF (grid_type/=unstructured) THEN
    119119      IF (n_lon.NE.nbp_lon) THEN
    120          print *,'Le nombre de lon n est pas egal a nbp_lon'
     120         PRINT *,'Le nombre de lon n est pas egal a nbp_lon'
    121121         STOP
    122122      ENDIF
     
    127127    CALL nf95_gw_var(ncid_in, varid, time)
    128128    n_month = size(time)
    129     print *, 'TIME aerosol strato=', n_month, time
     129    PRINT *, 'TIME aerosol strato=', n_month, time
    130130    IF (n_month.NE.12) THEN
    131        print *,'Le nombre de month n est pas egal a 12'
     131       PRINT *,'Le nombre de month n est pas egal a 12'
    132132       STOP
    133133    ENDIF
     
    140140    CALL nf95_inq_varid(ncid_in, "TAUSTRAT", varid)
    141141    ncerr = nf90_get_var(ncid_in, varid, tauaerstrat)
    142     print *,'code erreur readaerosolstrato=', ncerr, varid
     142    PRINT *,'code erreur readaerosolstrato=', ncerr, varid
    143143
    144144    CALL nf95_close(ncid_in)
     
    146146!---select the correct month
    147147    IF (mth_cur.LT.1.OR.mth_cur.GT.12) THEN
    148       print *,'probleme avec le mois dans readaerosolstrat =', mth_cur
     148      PRINT *,'probleme avec le mois dans readaerosolstrat =', mth_cur
    149149    ENDIF
    150150    tauaerstrat_mois(:,:,:) = tauaerstrat(:,:,:,mth_cur)
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/readaerosolstrato2_rrtm.F90

    r5159 r5160  
    9292!--check mth_cur
    9393        IF (mth_cur.LT.1.OR.mth_cur.GT.12) THEN
    94           print *,'probleme avec le mois dans readaerosolstrat =', mth_cur
     94          PRINT *,'probleme avec le mois dans readaerosolstrat =', mth_cur
    9595        ENDIF
    9696
     
    116116        IF (grid_type/=unstructured) THEN
    117117           IF (n_lat.NE.nbp_lat) THEN
    118              print *, 'latitude=', n_lat, nbp_lat
     118             PRINT *, 'latitude=', n_lat, nbp_lat
    119119             abort_message='Le nombre de lat n est pas egal a nbp_lat'
    120120             CALL abort_physic(modname,abort_message,1)
     
    133133        CALL nf95_gw_var(ncid_in, varid, wav)
    134134        n_wav = size(wav)
    135         print *, 'WAV aerosol strato=', n_wav, wav
     135        PRINT *, 'WAV aerosol strato=', n_wav, wav
    136136        IF (n_wav.NE.NSW) THEN
    137137           abort_message='Le nombre de wav n est pas egal a NSW'
     
    146146        CALL nf95_inq_varid(ncid_in, "TAU_SUN", varid)
    147147        ncerr = nf90_get_var(ncid_in, varid, tauaerstrat)
    148         print *,'code erreur readaerosolstrato=', ncerr, varid
     148        PRINT *,'code erreur readaerosolstrato=', ncerr, varid
    149149
    150150!--reading stratospheric aerosol omega per layer
    151151        CALL nf95_inq_varid(ncid_in, "OME_SUN", varid)
    152152        ncerr = nf90_get_var(ncid_in, varid, pizaerstrat)
    153         print *,'code erreur readaerosolstrato=', ncerr, varid
     153        PRINT *,'code erreur readaerosolstrato=', ncerr, varid
    154154
    155155!--reading stratospheric aerosol g per layer
    156156        CALL nf95_inq_varid(ncid_in, "GGG_SUN", varid)
    157157        ncerr = nf90_get_var(ncid_in, varid, cgaerstrat)
    158         print *,'code erreur readaerosolstrato sw=', ncerr, varid
     158        PRINT *,'code erreur readaerosolstrato sw=', ncerr, varid
    159159
    160160        CALL nf95_close(ncid_in)
     
    224224        CALL nf95_gw_var(ncid_in, varid, wav)
    225225        n_wav = size(wav)
    226         print *, 'WAV aerosol strato=', n_wav, wav
     226        PRINT *, 'WAV aerosol strato=', n_wav, wav
    227227        IF (n_wav.NE.NLW) THEN
    228228           abort_message='Le nombre de wav n est pas egal a NLW'
     
    235235        CALL nf95_inq_varid(ncid_in, "TAU_EAR", varid)
    236236        ncerr = nf90_get_var(ncid_in, varid, taulwaerstrat)
    237         print *,'code erreur readaerosolstrato lw=', ncerr, varid
     237        PRINT *,'code erreur readaerosolstrato lw=', ncerr, varid
    238238
    239239        CALL nf95_close(ncid_in)
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/rrtm_rtrn1a_140gp.F90

    r5133 r5160  
    529529DO I_LEV = 1, KLEV
    530530  DO IBAND = K_ISTART, K_IEND
    531 ! print *,'RTRN1A: I_LEV JPLAY IBAND INDLAY',I_LEV,JPLAY,IBAND,INDLAY(I_LEV)
     531! PRINT *,'RTRN1A: I_LEV JPLAY IBAND INDLAY',I_LEV,JPLAY,IBAND,INDLAY(I_LEV)
    532532!----             
    533533!- Calculate the integrated Planck functions for at the
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/srtm_cldprop.F90

    r1990 r5160  
    116116
    117117IF (I_NDBUG <= 2) THEN
    118   print *,'cldprop before loop K_INFLAG, K_ICEFLAG, K_LIQFLAG:',K_INFLAG,K_ICEFLAG,K_LIQFLAG,IB1,IB2
     118  PRINT *,'cldprop before loop K_INFLAG, K_ICEFLAG, K_LIQFLAG:',K_INFLAG,K_ICEFLAG,K_LIQFLAG,IB1,IB2
    119119ENDIF
    120120
     
    216216        ENDDO
    217217      ENDIF
    218       print *,'end of ice computations for I_LAY=',I_LAY
     218      PRINT *,'end of ice computations for I_LAY=',I_LAY
    219219                 
    220220!  Calculation of absorption coefficients due to water clouds.
     
    270270
    271271      IF (I_NDBUG <= 1) THEN
    272         print *,'end of liquid water computations for I_LAY=',I_LAY
     272        PRINT *,'end of liquid water computations for I_LAY=',I_LAY
    273273      ENDIF
    274274
     
    332332
    333333IF (I_NDBUG <= 1) THEN
    334   print *,'about to leave SRTM_CLDPROP'
     334  PRINT *,'about to leave SRTM_CLDPROP'
    335335ENDIF
    336336
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/srtm_setcoef.F90

    r1990 r5160  
    9494
    9595!IF (NDBUG.LE.3) THEN
    96 print *,'-------- Computed in SETCOEF --------'
     96PRINT *,'-------- Computed in SETCOEF --------'
    9797!  print 8990
    98988990 format(18x,'  T     PFAC00,    01,    10,    11  PCO2MULT     MOL   &
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/srtm_spcvrt.F90

    r1990 r5160  
    203203IB1=JPB1
    204204IB2=JPB2
    205 !print *,'IB1, IB2, KSW, KMOL, KLEV: ', IB1,IB2,KSW,KMOL,KLEV
     205!PRINT *,'IB1, IB2, KSW, KMOL, KLEV: ', IB1,IB2,KSW,KMOL,KLEV
    206206
    207207IW=0
     
    215215  ZINCF14(IBM)=0.0_JPRB
    216216
    217 print *,'=== spectral band === JB= ',JB,' ====== i.e. IBM= ',IBM,' with IGT= ',IGT
     217PRINT *,'=== spectral band === JB= ',JB,' ====== i.e. IBM= ',IBM,' with IGT= ',IGT
    218218       
    219219!-- for each band, computes the gaseous and Rayleigh optical thickness
     
    229229     &   ZSFLXZEN, ZTAUG    , ZTAUR    &
    230230     & ) 
    231 !    print *,'After  SRTM_TAUMOL16'
     231!    PRINT *,'After  SRTM_TAUMOL16'
    232232
    233233  ELSEIF (JB == 17) THEN
     
    240240     &   ZSFLXZEN, ZTAUG   , ZTAUR    &
    241241     & ) 
    242 !    print *,'After  SRTM_TAUMOL17'
     242!    PRINT *,'After  SRTM_TAUMOL17'
    243243
    244244  ELSEIF (JB == 18) THEN
     
    251251     &   ZSFLXZEN, ZTAUG   , ZTAUR    &
    252252     & ) 
    253 !    print *,'After  SRTM_TAUMOL18'
     253!    PRINT *,'After  SRTM_TAUMOL18'
    254254
    255255  ELSEIF (JB == 19) THEN
     
    262262     &   ZSFLXZEN, ZTAUG   , ZTAUR    &
    263263     & ) 
    264 !    print *,'After  SRTM_TAUMOL19'
     264!    PRINT *,'After  SRTM_TAUMOL19'
    265265
    266266  ELSEIF (JB == 20) THEN
     
    273273     &   ZSFLXZEN, ZTAUG   , ZTAUR    &
    274274     & ) 
    275 !    print *,'After  SRTM_TAUMOL20'
     275!    PRINT *,'After  SRTM_TAUMOL20'
    276276
    277277  ELSEIF (JB == 21) THEN
     
    284284     &   ZSFLXZEN, ZTAUG   , ZTAUR    &
    285285     & ) 
    286 !    print *,'After  SRTM_TAUMOL21'
     286!    PRINT *,'After  SRTM_TAUMOL21'
    287287
    288288  ELSEIF (JB == 22) THEN
     
    295295     &   ZSFLXZEN, ZTAUG   , ZTAUR    &
    296296     & ) 
    297 !    print *,'After  SRTM_TAUMOL22'
     297!    PRINT *,'After  SRTM_TAUMOL22'
    298298
    299299  ELSEIF (JB == 23) THEN
     
    306306     &   ZSFLXZEN, ZTAUG   , ZTAUR    &
    307307     & ) 
    308 !    print *,'After  SRTM_TAUMOL23'
     308!    PRINT *,'After  SRTM_TAUMOL23'
    309309
    310310  ELSEIF (JB == 24) THEN
     
    317317     &   ZSFLXZEN, ZTAUG   , ZTAUR    &
    318318     & ) 
    319 !    print *,'After  SRTM_TAUMOL24'
     319!    PRINT *,'After  SRTM_TAUMOL24'
    320320
    321321  ELSEIF (JB == 25) THEN
     
    329329     &   ZSFLXZEN, ZTAUG   , ZTAUR   &
    330330     & ) 
    331 !    print *,'After  SRTM_TAUMOL25'
     331!    PRINT *,'After  SRTM_TAUMOL25'
    332332
    333333  ELSEIF (JB == 26) THEN
     
    341341     &   ZSFLXZEN, ZTAUG   , ZTAUR    &
    342342     & ) 
    343 !    print *,'After  SRTM_TAUMOL26'
     343!    PRINT *,'After  SRTM_TAUMOL26'
    344344
    345345  ELSEIF (JB == 27) THEN
     
    353353     &   ZSFLXZEN, ZTAUG   , ZTAUR    &
    354354     & ) 
    355 !    print *,'After  SRTM_TAUMOL27'
     355!    PRINT *,'After  SRTM_TAUMOL27'
    356356
    357357  ELSEIF (JB == 28) THEN
     
    365365     &   ZSFLXZEN, ZTAUG   , ZTAUR  &
    366366     & ) 
    367 !    print *,'After  SRTM_TAUMOL28'
     367!    PRINT *,'After  SRTM_TAUMOL28'
    368368
    369369  ELSEIF (JB == 29) THEN
     
    376376     &   ZSFLXZEN , ZTAUG   , ZTAUR    &
    377377     & ) 
    378 !    print *,'After  SRTM_TAUMOL29'
     378!    PRINT *,'After  SRTM_TAUMOL29'
    379379
    380380  ENDIF
    381381
    382382!  IF (NDBUG.LE.3) THEN
    383 !    print *,'Incident Solar Flux'
     383!    PRINT *,'Incident Solar Flux'
    384384!    PRINT 9010,(ZSFLXZEN(JG),JG=1,16)
    385385  9010 format(1x,'SolFlx ',16F8.4)
    386 !    print *,'Optical thickness for molecular absorption for JB= ',JB
     386!    PRINT *,'Optical thickness for molecular absorption for JB= ',JB
    387387!    DO JK=1,KLEV
    388388!      PRINT 9011,JK,(ZTAUG(JK,JG),JG=1,16)
    389389  9011  format(1x,'TauGas ',I3,16E9.2)
    390390!    ENDDO
    391 !    print *,'Optical thickness for Rayleigh scattering for JB= ',JB
     391!    PRINT *,'Optical thickness for Rayleigh scattering for JB= ',JB
    392392!    DO JK=1,KLEV
    393393!      PRINT 9012,JK,(ZTAUR(JK,JG),JG=1,16)
    394394  9012  format(1x,'TauRay ',I3,16E9.2)
    395395!    ENDDO
    396 !    print *,'Cloud optical properties for JB= ',JB
     396!    PRINT *,'Cloud optical properties for JB= ',JB
    397397!    DO JK=1,KLEV
    398398!      PRINT 9013,JK,PFRCL(JK),PTAUC(JK,IBM),POMGC(JK,IBM),PASYC(JK,IBM)
     
    405405
    406406!    IF (NDBUG.LE.1) THEN
    407 !      print *,' === JG= ',JG,' === for JB= ',JB,' with IW, IBM, JPLAY, KLEV=',IW,IBM,JPLAY,KLEV
     407!      PRINT *,' === JG= ',JG,' === for JB= ',JB,' with IW, IBM, JPLAY, KLEV=',IW,IBM,JPLAY,KLEV
    408408!    ENDIF
    409409
     
    460460    ZRUP(KLEV+1) =PALBP(IBM)
    461461    ZRUPD(KLEV+1)=PALBD(IBM)
    462 !    if (NDBUG < 2) print *,'SWSPCTRL after 1 with JB,JG,IBM and IW= ',JB,JG,IBM,IW
     462!    if (NDBUG < 2) PRINT *,'SWSPCTRL after 1 with JB,JG,IBM and IW= ',JB,JG,IBM,IW
    463463   
    464464    DO JK=1,KLEV
     
    511511!      end if
    512512    ENDDO   
    513 !    if (NDBUG < 2) print *,'SWSPCTRL after 2'
     513!    if (NDBUG < 2) PRINT *,'SWSPCTRL after 2'
    514514
    515515!-- Delta scaling for clear-sky / aerosol optical quantities
     
    525525     &   LLRTCHK, ZGCC  , PRMU0, ZTAUC , ZOMCC ,&
    526526     &   ZREFC  , ZREFDC, ZTRAC, ZTRADC ) 
    527 !    if (NDBUG < 2) print *,'SWSPCTR after SWREFTRA for clear-sky'
     527!    if (NDBUG < 2) PRINT *,'SWSPCTR after SWREFTRA for clear-sky'
    528528   
    529529!-- Delta scaling for cloudy quantities
     
    545545
    546546    ENDDO
    547 !    if (NDBUG < 2) print *,'SWSPCTR after Delta scaling'
     547!    if (NDBUG < 2) PRINT *,'SWSPCTR after Delta scaling'
    548548   
    549549    CALL SRTM_REFTRA ( KLEV, I_KMODTS ,&
    550550     &   LLRTCHK, ZGCO  , PRMU0, ZTAUO , ZOMCO ,&
    551551     &   ZREFO , ZREFDO, ZTRAO, ZTRADO ) 
    552 !    if (NDBUG < 2) print *,'SWSPCTR after SWREFTRA for cloudy'
     552!    if (NDBUG < 2) PRINT *,'SWSPCTR after SWREFTRA for cloudy'
    553553
    554554    DO JK=1,KLEV
     
    582582
    583583    ENDDO           
    584 !    if (NDBUG < 2) print *,'SRTM_SPCVRT after combining clear and cloudy'
     584!    if (NDBUG < 2) PRINT *,'SRTM_SPCVRT after combining clear and cloudy'
    585585                 
    586586!-- vertical quadrature producing clear-sky fluxes
    587587
    588 !    print *,'SRTM_SPCVRT after 3 before SRTM_VRTQDR clear'
     588!    PRINT *,'SRTM_SPCVRT after 3 before SRTM_VRTQDR clear'
    589589   
    590590    CALL SRTM_VRTQDR ( KLEV, IW ,&
     
    594594     
    595595!    IF (NDBUG < 2) THEN
    596 !      print *,'SRTM_SPCVRT out of SRTM_VRTQDR for clear IW=',IW 
     596!      PRINT *,'SRTM_SPCVRT out of SRTM_VRTQDR for clear IW=',IW
    597597!      DO JK=1,KLEV+1
    598598!        print 9201,JK,ZCD(JK,IW),ZCU(JK,IW)
     
    603603!-- vertical quadrature producing cloudy fluxes
    604604
    605 !    print *,'SRTM_SPCVRT after 4 before SRTM_VRTQDR cloudy'
     605!    PRINT *,'SRTM_SPCVRT after 4 before SRTM_VRTQDR cloudy'
    606606   
    607607    CALL SRTM_VRTQDR ( KLEV, IW ,&
     
    611611 
    612612!    IF (NDBUG < 2) THEN     
    613 !      print *,'SRTM_SPCVRT out of SRTM_VRTQDR for cloudy IW=',IW
     613!      PRINT *,'SRTM_SPCVRT out of SRTM_VRTQDR for cloudy IW=',IW
    614614!      DO JK=1,KLEV+1
    615615!        print 9202,JK,ZFD(JK,IW),ZFU(JK,IW)
     
    655655    ENDDO
    656656
    657 !    if (NDBUG < 2) print *,'SRTM_SPCVRT end of JG=',JG,' for JB=',JB,' i.e. IW=',IW
     657!    if (NDBUG < 2) PRINT *,'SRTM_SPCVRT end of JG=',JG,' for JB=',JB,' i.e. IW=',IW
    658658  ENDDO             
    659659!-- end loop on JG
    660660
    661 print *,' --- JB= ',JB,' with IB1, IB2= ',IB1,IB2
     661PRINT *,' --- JB= ',JB,' with IB1, IB2= ',IB1,IB2
    662662ENDDO                   
    663663!-- end loop on JB
    664 !if (NDBUG < 2) print *,'SRTM_SPCVRT about to come out'
     664!if (NDBUG < 2) PRINT *,'SRTM_SPCVRT about to come out'
    665665
    666666!DO IBM=1,14
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/srtm_spcvrt_mcica.F90

    r1990 r5160  
    210210IB1=JPB1
    211211IB2=JPB2
    212 !print *,'IB1, IB2, KSW, KMOL, KLEV: ', IB1,IB2,KSW,KMOL,KLEV
     212!PRINT *,'IB1, IB2, KSW, KMOL, KLEV: ', IB1,IB2,KSW,KMOL,KLEV
    213213
    214214IW=0
     
    222222  ZINCF14(IBM)=0.0_JPRB
    223223
    224 print *,'=== spectral band === JB= ',JB,' ====== i.e. IBM= ',IBM,' with IGT= ',IGT
     224PRINT *,'=== spectral band === JB= ',JB,' ====== i.e. IBM= ',IBM,' with IGT= ',IGT
    225225       
    226226!-- for each band, computes the gaseous and Rayleigh optical thickness
     
    236236     &   ZSFLXZEN, ZTAUG    , ZTAUR    &
    237237     & ) 
    238 !    print *,'After  SRTM_TAUMOL16'
     238!    PRINT *,'After  SRTM_TAUMOL16'
    239239
    240240  ELSEIF (JB == 17) THEN
     
    247247     &   ZSFLXZEN, ZTAUG   , ZTAUR    &
    248248     & ) 
    249 !    print *,'After  SRTM_TAUMOL17'
     249!    PRINT *,'After  SRTM_TAUMOL17'
    250250
    251251  ELSEIF (JB == 18) THEN
     
    258258     &   ZSFLXZEN, ZTAUG   , ZTAUR    &
    259259     & ) 
    260 !    print *,'After  SRTM_TAUMOL18'
     260!    PRINT *,'After  SRTM_TAUMOL18'
    261261
    262262  ELSEIF (JB == 19) THEN
     
    269269     &   ZSFLXZEN, ZTAUG   , ZTAUR    &
    270270     & ) 
    271 !    print *,'After  SRTM_TAUMOL19'
     271!    PRINT *,'After  SRTM_TAUMOL19'
    272272
    273273  ELSEIF (JB == 20) THEN
     
    280280     &   ZSFLXZEN, ZTAUG   , ZTAUR    &
    281281     & ) 
    282 !    print *,'After  SRTM_TAUMOL20'
     282!    PRINT *,'After  SRTM_TAUMOL20'
    283283
    284284  ELSEIF (JB == 21) THEN
     
    291291     &   ZSFLXZEN, ZTAUG   , ZTAUR    &
    292292     & ) 
    293 !    print *,'After  SRTM_TAUMOL21'
     293!    PRINT *,'After  SRTM_TAUMOL21'
    294294
    295295  ELSEIF (JB == 22) THEN
     
    302302     &   ZSFLXZEN, ZTAUG   , ZTAUR    &
    303303     & ) 
    304 !    print *,'After  SRTM_TAUMOL22'
     304!    PRINT *,'After  SRTM_TAUMOL22'
    305305
    306306  ELSEIF (JB == 23) THEN
     
    313313     &   ZSFLXZEN, ZTAUG   , ZTAUR    &
    314314     & ) 
    315 !    print *,'After  SRTM_TAUMOL23'
     315!    PRINT *,'After  SRTM_TAUMOL23'
    316316
    317317  ELSEIF (JB == 24) THEN
     
    324324     &   ZSFLXZEN, ZTAUG   , ZTAUR    &
    325325     & ) 
    326 !    print *,'After  SRTM_TAUMOL24'
     326!    PRINT *,'After  SRTM_TAUMOL24'
    327327
    328328  ELSEIF (JB == 25) THEN
     
    336336     &   ZSFLXZEN, ZTAUG   , ZTAUR   &
    337337     & ) 
    338 !    print *,'After  SRTM_TAUMOL25'
     338!    PRINT *,'After  SRTM_TAUMOL25'
    339339
    340340  ELSEIF (JB == 26) THEN
     
    348348     &   ZSFLXZEN, ZTAUG   , ZTAUR    &
    349349     & ) 
    350 !    print *,'After  SRTM_TAUMOL26'
     350!    PRINT *,'After  SRTM_TAUMOL26'
    351351
    352352  ELSEIF (JB == 27) THEN
     
    360360     &   ZSFLXZEN, ZTAUG   , ZTAUR    &
    361361     & ) 
    362 !    print *,'After  SRTM_TAUMOL27'
     362!    PRINT *,'After  SRTM_TAUMOL27'
    363363
    364364  ELSEIF (JB == 28) THEN
     
    372372     &   ZSFLXZEN, ZTAUG   , ZTAUR  &
    373373     & ) 
    374 !    print *,'After  SRTM_TAUMOL28'
     374!    PRINT *,'After  SRTM_TAUMOL28'
    375375
    376376  ELSEIF (JB == 29) THEN
     
    383383     &   ZSFLXZEN , ZTAUG   , ZTAUR    &
    384384     & ) 
    385 !    print *,'After  SRTM_TAUMOL29'
     385!    PRINT *,'After  SRTM_TAUMOL29'
    386386
    387387  ENDIF
    388388
    389389!  IF (NDBUG.LE.3) THEN
    390 !    print *,'Incident Solar Flux'
     390!    PRINT *,'Incident Solar Flux'
    391391!    PRINT 9010,(ZSFLXZEN(JG),JG=1,16)
    392392  9010 format(1x,'SolFlx ',16F8.4)
    393 !    print *,'Optical thickness for molecular absorption for JB= ',JB
     393!    PRINT *,'Optical thickness for molecular absorption for JB= ',JB
    394394!    DO JK=1,KLEV
    395395!      PRINT 9011,JK,(ZTAUG(JK,JG),JG=1,16)
    396396  9011  format(1x,'TauGas ',I3,16E9.2)
    397397!    ENDDO
    398 !    print *,'Optical thickness for Rayleigh scattering for JB= ',JB
     398!    PRINT *,'Optical thickness for Rayleigh scattering for JB= ',JB
    399399!    DO JK=1,KLEV
    400400!      PRINT 9012,JK,(ZTAUR(JK,JG),JG=1,16)
     
    407407
    408408!    IF (NDBUG.LE.1) THEN
    409 !      print *,' === JG= ',JG,' === for JB= ',JB,' with IW, IBM, JPLAY, KLEV=',IW,IBM,JPLAY,KLEV
     409!      PRINT *,' === JG= ',JG,' === for JB= ',JB,' with IW, IBM, JPLAY, KLEV=',IW,IBM,JPLAY,KLEV
    410410!    ENDIF
    411411!    IF (NDBUG.LE.3) THEN
    412 !      print *,'Cloud optical properties for JB= ',JB
     412!      PRINT *,'Cloud optical properties for JB= ',JB
    413413!      DO JK=1,KLEV
    414414!        PRINT 9013,JK,PFRCL(IW,JK),PTAUC(JK,IW),POMGC(JK,IW),PASYC(JK,IW)
     
    469469    ZRUP(KLEV+1) =PALBP(IBM)
    470470    ZRUPD(KLEV+1)=PALBD(IBM)
    471 !    if (NDBUG < 2) print *,'SWSPCTRL after 1 with JB,JG,IBM and IW= ',JB,JG,IBM,IW
     471!    if (NDBUG < 2) PRINT *,'SWSPCTRL after 1 with JB,JG,IBM and IW= ',JB,JG,IBM,IW
    472472   
    473473
     
    523523!      end if
    524524    ENDDO   
    525 !    if (NDBUG < 2) print *,'SWSPCTRL after 2'
     525!    if (NDBUG < 2) PRINT *,'SWSPCTRL after 2'
    526526
    527527!-- Delta scaling for clear-sky / aerosol optical quantities
     
    537537     &   LLRTCHK, ZGCC  , PRMU0, ZTAUC , ZOMCC ,&
    538538     &   ZREFC  , ZREFDC, ZTRAC, ZTRADC ) 
    539 !    if (NDBUG < 2) print *,'SWSPCTR after SWREFTRA for clear-sky'
     539!    if (NDBUG < 2) PRINT *,'SWSPCTR after SWREFTRA for clear-sky'
    540540   
    541541!-- Delta scaling for cloudy quantities
     
    557557
    558558    ENDDO
    559 !    if (NDBUG < 2) print *,'SWSPCTR after Delta scaling'
     559!    if (NDBUG < 2) PRINT *,'SWSPCTR after Delta scaling'
    560560   
    561561    CALL SRTM_REFTRA ( KLEV, I_KMODTS ,&
    562562     &   LLRTCHK, ZGCO  , PRMU0, ZTAUO , ZOMCO ,&
    563563     &   ZREFO , ZREFDO, ZTRAO, ZTRADO ) 
    564 !    if (NDBUG < 2) print *,'SWSPCTR after SWREFTRA for cloudy'
     564!    if (NDBUG < 2) PRINT *,'SWSPCTR after SWREFTRA for cloudy'
    565565
    566566    DO JK=1,KLEV
     
    606606
    607607    ENDDO           
    608 !    if (NDBUG < 2) print *,'SRTM_SPCVRT after combining clear and cloudy'
     608!    if (NDBUG < 2) PRINT *,'SRTM_SPCVRT after combining clear and cloudy'
    609609                 
    610610!-- vertical quadrature producing clear-sky fluxes
    611611
    612 !    print *,'SRTM_SPCVRT after 3 before SRTM_VRTQDR clear'
     612!    PRINT *,'SRTM_SPCVRT after 3 before SRTM_VRTQDR clear'
    613613   
    614614    CALL SRTM_VRTQDR ( KLEV, IW ,&
     
    618618     
    619619!    IF (NDBUG < 2) THEN
    620 !      print *,'SRTM_SPCVRT out of SRTM_VRTQDR for clear IW=',IW 
     620!      PRINT *,'SRTM_SPCVRT out of SRTM_VRTQDR for clear IW=',IW
    621621!      DO JK=1,KLEV+1
    622622!        print 9201,JK,ZCD(JK,IW),ZCU(JK,IW)
     
    627627!-- vertical quadrature producing cloudy fluxes
    628628
    629 !    print *,'SRTM_SPCVRT after 4 before SRTM_VRTQDR cloudy'
     629!    PRINT *,'SRTM_SPCVRT after 4 before SRTM_VRTQDR cloudy'
    630630   
    631631    CALL SRTM_VRTQDR ( KLEV, IW ,&
     
    635635 
    636636!    IF (NDBUG < 2) THEN     
    637 !      print *,'SRTM_SPCVRT out of SRTM_VRTQDR for cloudy IW=',IW
     637!      PRINT *,'SRTM_SPCVRT out of SRTM_VRTQDR for cloudy IW=',IW
    638638!      DO JK=1,KLEV+1
    639639!        print 9202,JK,ZFD(JK,IW),ZFU(JK,IW)
     
    679679    ENDDO
    680680
    681 !    if (NDBUG < 2) print *,'SRTM_SPCVRT end of JG=',JG,' for JB=',JB,' i.e. IW=',IW
     681!    if (NDBUG < 2) PRINT *,'SRTM_SPCVRT end of JG=',JG,' for JB=',JB,' i.e. IW=',IW
    682682  ENDDO             
    683683!-- end loop on JG
    684684
    685 print *,' --- JB= ',JB,' with IB1, IB2= ',IB1,IB2
     685PRINT *,' --- JB= ',JB,' with IB1, IB2= ',IB1,IB2
    686686ENDDO                   
    687687!-- end loop on JB
    688 !if (NDBUG < 2) print *,'SRTM_SPCVRT about to come out'
    689 !print *,'SRTM_SPCVRT about to come out'
     688!if (NDBUG < 2) PRINT *,'SRTM_SPCVRT about to come out'
     689!PRINT *,'SRTM_SPCVRT about to come out'
    690690
    691691!DO IBM=1,14
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/srtm_srtm_224gp.F90

    r5159 r5160  
    133133  IOVLP = 3
    134134
    135   !print *,'Entering srtm_srtm_224gp'
     135  !PRINT *,'Entering srtm_srtm_224gp'
    136136
    137137  ICLDATM = 1
     
    148148      !- coefficients related to the cloud optical properties (original RRTM_SW)
    149149
    150       !  print *,'just before SRTM_CLDPROP'
     150      !  PRINT *,'just before SRTM_CLDPROP'
    151151
    152152      !  DO JK=1,KLEV
     
    218218      ENDDO
    219219
    220       !  print *,'ZTOTCC ZCLEAR : ',ZTOTCC,' ',ZCLEAR
     220      !  PRINT *,'ZTOTCC ZCLEAR : ',ZTOTCC,' ',ZCLEAR
    221221
    222222      DO IMOL = 1, I_NMOL
     
    236236      !    ENDIF
    237237
    238       !  print *,'just before SRTM_SETCOEF'
     238      !  PRINT *,'just before SRTM_SETCOEF'
    239239
    240240      ZFRCL(1:KLEV) = PFRCL(JL, 1:KLEV)
     
    253253              &)
    254254
    255       !  print *,'just after SRTM_SETCOEF'
     255      !  PRINT *,'just after SRTM_SETCOEF'
    256256
    257257      !- call the radiation transfer routine
     
    271271      !- mixing of aerosols
    272272
    273       !  print *,'Aerosol optical properties computations'
     273      !  PRINT *,'Aerosol optical properties computations'
    274274      !  DO JSW=1,KSW
    275275      !    print 9012,JSW,(JAE,RSRTAUA(JSW,JAE),RSRPIZA(JSW,JAE),RSRASYA(JSW,JAE),JAE=1,6)
     
    335335      ENDDO
    336336
    337       !  print *,'just before calling STRM_SPCVRT for JL=',JL,' and ZRMU0=',ZRMU0
     337      !  PRINT *,'just before calling STRM_SPCVRT for JL=',JL,' and ZRMU0=',ZRMU0
    338338
    339339      CALL SRTM_SPCVRT &
     
    351351              &)
    352352
    353       !  print *,'SRTM_SRTM_224GP before potential scaling'
     353      !  PRINT *,'SRTM_SRTM_224GP before potential scaling'
    354354      !    IF (IOVLP == 3) THEN
    355355      !      DO JK=1,KLEV+1
     
    362362      !      ENDDO
    363363      !    ELSE
    364       !    print *,'SRTM_SRTM_224GP after potential scaling'
     364      !    PRINT *,'SRTM_SRTM_224GP after potential scaling'
    365365      DO JK = 1, KLEV + 1
    366366        PFSUC(JL, 1, JK) = ZADJI0 * ZBBCU(JK)
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/srtm_srtm_224gp_mcica.F90

    r5154 r5160  
    144144  IOVLP = 3
    145145
    146   !print *,'Entering srtm_srtm_224gp_mcica'
     146  !PRINT *,'Entering srtm_srtm_224gp_mcica'
    147147
    148148  ICLDATM = 1
     
    159159      !- coefficients related to the cloud optical properties (original RRTM_SW)
    160160
    161       !  print *,'just before SRTM_CLDPROP'
     161      !  PRINT *,'just before SRTM_CLDPROP'
    162162
    163163      !  DO JK=1,KLEV
     
    214214      ENDDO
    215215
    216       !  print *,'ZTOTCC ZCLEAR : ',ZTOTCC,' ',ZCLEAR
     216      !  PRINT *,'ZTOTCC ZCLEAR : ',ZTOTCC,' ',ZCLEAR
    217217
    218218      DO IMOL = 1, ITMOL
     
    222222      ENDDO
    223223
    224       !  print *,'just before SRTM_SETCOEF'
     224      !  PRINT *,'just before SRTM_SETCOEF'
    225225
    226226      CALL SRTM_SETCOEF &
     
    235235              &)
    236236
    237       !  print *,'just after SRTM_SETCOEF'
     237      !  PRINT *,'just after SRTM_SETCOEF'
    238238
    239239      !- call the radiation transfer routine
     
    265265      !- mixing of aerosols
    266266
    267       !  print *,'Aerosol optical properties computations'
     267      !  PRINT *,'Aerosol optical properties computations'
    268268      !  DO JSW=1,KSW
    269269      !    print 9012,JSW,(JAE,RSRTAUA(JSW,JAE),RSRPIZA(JSW,JAE),RSRASYA(JSW,JAE),JAE=1,6)
     
    329329      ENDDO
    330330
    331       !    print *,'just before calling STRM_SPCVRT for JL=',JL,' and ZRMU0=',ZRMU0
     331      !    PRINT *,'just before calling STRM_SPCVRT for JL=',JL,' and ZRMU0=',ZRMU0
    332332
    333333      CALL SRTM_SPCVRT_MCICA &
     
    347347      !     & )
    348348
    349       !  print *,'SRTM_SRTM_224GP before potential scaling'
     349      !  PRINT *,'SRTM_SRTM_224GP before potential scaling'
    350350      !    IF (IOVLP == 3) THEN
    351351      !      DO JK=1,KLEV+1
     
    358358      !      ENDDO
    359359      !    ELSE
    360       !    print *,'SRTM_SRTM_224GP after potential scaling'
     360      !    PRINT *,'SRTM_SRTM_224GP after potential scaling'
    361361      DO JK = 1, KLEV + 1
    362362        PFSUC(JL, 1, JK) = ZADJI0 * ZBBCU(JK)
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/srtm_vrtqdr.F90

    r1990 r5160  
    114114!  print 9201,PRUP(KLEV),PRUPD(KLEV)
    1151159201 format(1x,'link surf:',6E13.6)
    116 print *,'SRTM_VRTQDR after linking with surface layer'
     116PRINT *,'SRTM_VRTQDR after linking with surface layer'
    117117!END IF
    118118   
     
    134134  9203 format(1x,'bot2top:',6E13.6)
    135135ENDDO
    136 !print *,'SRTM_VRTQDR after passing from bottom to top'
     136!PRINT *,'SRTM_VRTQDR after passing from bottom to top'
    137137   
    138138!-- upper boundary conditions
     
    146146!  print 9204,ZTDN(1),PRDND(1),ZTDN(2),PRDND(2)
    1471479204 format(1x,'link upper bound:',6E13.6)
    148 print *,'SRTM_VRTQDR after upper boundary conditions'
     148PRINT *,'SRTM_VRTQDR after upper boundary conditions'
    149149!END IF
    150150   
     
    166166
    167167ENDDO
    168 !print *,'SRTM_VRTQDR after passing from top to bottom'
     168!PRINT *,'SRTM_VRTQDR after passing from top to bottom'
    169169                                             
    170170!-- up and down-welling fluxes at levels
     
    190190
    191191ENDDO
    192 !print *,'SRTM_VRTQDR after up and down flux'
     192!PRINT *,'SRTM_VRTQDR after up and down flux'
    193193   
    194 !print *,'SRTM_VRTQDR about to come out'
     194!PRINT *,'SRTM_VRTQDR about to come out'
    195195!     ------------------------------------------------------------------
    196196
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/su_aerw.F90

    r5158 r5160  
    9090!                   ----------------------------
    9191
    92 print *,'DANS SU_AERW'
     92PRINT *,'DANS SU_AERW'
    9393NBINAER(:) = (/ 3, 3, 2, 2, 1, 1, 1, 1, 1 /)
    9494
     
    166166
    167167  CALL SU_AERP
    168 print *,'SU_AERW: apres SU_AERP'
     168PRINT *,'SU_AERW: apres SU_AERP'
    169169  CALL SU_AEROP
    170 print *,'SU_AERW: apres SU_AEROP'
     170PRINT *,'SU_AERW: apres SU_AEROP'
    171171
    172172IF (LEPAERO) THEN
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/sucst.F90

    r5158 r5160  
    202202RBETW=RLVTT/RV+RGAMW*RTT
    203203RALPW=LOG(RESTT)+RBETW/RTT+RGAMW*LOG(RTT)
    204 print *,'SUCST: RESTT,RBETW,RTT,RGAMW',RESTT,RBETW,RTT,RGAMW
    205 print *,'SUCST: RALPW',RALPW
     204PRINT *,'SUCST: RESTT,RBETW,RTT,RGAMW',RESTT,RBETW,RTT,RGAMW
     205PRINT *,'SUCST: RALPW',RALPW
    206206RGAMS=(RCS-RCPV)/RV
    207207RBETS=RLSTT/RV+RGAMS*RTT
    208208RALPS=LOG(RESTT)+RBETS/RTT+RGAMS*LOG(RTT)
    209 print *,'SUCST: RESTT,RBETS,RTT,RGAMS',RESTT,RBETS,RTT,RGAMS
    210 print *,'SUCST: RALPS',RALPS
     209PRINT *,'SUCST: RESTT,RBETS,RTT,RGAMS',RESTT,RBETS,RTT,RGAMS
     210PRINT *,'SUCST: RALPS',RALPS
    211211RGAMS=(RCS-RCPV)/RV
    212212RGAMD=RGAMS-RGAMW
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/suecrad.F90

    r5159 r5160  
    295295  NRADIP = 3            ! before 3?R1 default=2     3
    296296  NRADLP = 2            ! before 3?R1 default=2    2
    297   print *, 'SUECRAD: NRADLP, NRADIP=', NRADLP, NRADIP
     297  PRINT *, 'SUECRAD: NRADLP, NRADIP=', NRADLP, NRADIP
    298298  RRe2De = 0.64952_JPRB ! before 3?R1 default=0.5_JPRB
    299299
     
    345345  !- interaction radiation / prognostic O3 off by default
    346346  LEPO3RA = .FALSE.
    347   print *, 'SUECRAD-0'
     347  PRINT *, 'SUECRAD-0'
    348348  IF (.NOT.YO3%LGP) THEN
    349349    LEPO3RA = .FALSE.
     
    407407    NOVLP = 1
    408408  END SELECT
    409   print *, 'SUECRAD: NOVLP=', NOVLP
     409  PRINT *, 'SUECRAD: NOVLP=', NOVLP
    410410  NLW = 16
    411411  NTSW = 14
     
    462462  RCCFC11 = CFC11_ppt * 1.0e-12
    463463  RCCFC12 = CFC12_ppt * 1.0e-12
    464   !print *,'LMDZSUECRAD-1 RCCO2=',RCCO2
    465   !print *,'LMDZSUECRAD-1 RCCH4=',RCCH4
    466   !print *,'LMDZSUECRAD-1 RCN2O=',RCN2O
    467   !print *,'LMDZSUECRAD-1 RCCFC11=',RCCFC11
    468   !print *,'LMDZSUECRAD-1 RCCFC12=',RCCFC12
     464  !PRINT *,'LMDZSUECRAD-1 RCCO2=',RCCO2
     465  !PRINT *,'LMDZSUECRAD-1 RCCH4=',RCCH4
     466  !PRINT *,'LMDZSUECRAD-1 RCN2O=',RCN2O
     467  !PRINT *,'LMDZSUECRAD-1 RCCFC11=',RCCFC11
     468  !PRINT *,'LMDZSUECRAD-1 RCCFC12=',RCCFC12
    469469  !     ------------------------------------------------------------------
    470470
     
    474474  !CALL POSNAM(NULNAM,'NAERAD')
    475475  !READ (NULNAM,NAERAD)
    476   print *, 'SUECRAD-2'
     476  PRINT *, 'SUECRAD-2'
    477477
    478478  !CALL POSNAM(NULNAM,'NAEAER')
     
    510510    RSWINHF = 0.7_JPRB
    511511  ENDIF
    512   print *, 'SUECRAD-3'
     512  PRINT *, 'SUECRAD-3'
    513513
    514514  !- for McICA computations, make sure these parameters are as follows ...
     
    520520    CALL SU_McICA
    521521  ENDIF
    522   print *, 'SUECRAD-4'
     522  PRINT *, 'SUECRAD-4'
    523523
    524524  IF(LLDEBUG)THEN
     
    613613        ENDIF
    614614      ENDIF
    615       print *, 'SUECRAD-5'
     615      PRINT *, 'SUECRAD-5'
    616616
    617617      ! test if radiation grid resolution has been set
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/suinit.F90

    r3435 r5160  
    9494!          NDLNPR=1: formulation of delta used in non hydrostatic model,
    9595NDLNPR=0
    96 print *,'SUINIT: RHYDR0 NDLNPR',RHYDR0,NDLNPR
     96PRINT *,'SUINIT: RHYDR0 NDLNPR',RHYDR0,NDLNPR
    9797
    9898!----------------------------------------------------------------
     
    114114NSSSSS=0  ! LMDZ demarre tjrs a 00h -- MPL 15.04.09
    115115CALL SUCST(6,NINDAT,NSSSSS,1)
    116 print *,'SUINIT: NINDAT, NSSSSS',NINDAT, NSSSSS
     116PRINT *,'SUINIT: NINDAT, NSSSSS',NINDAT, NSSSSS
    117117
    118118IF (LLDEBUG) THEN
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/suovlp.F90

    r1990 r5160  
    4343DO JK=1,KLEV
    4444  RA1OVLP(JK)=RAOVLP*STZ(JK)+RBOVLP
    45   print *,'SU_OVLP: JK RAOVLP STZ RBOVLP:',JK,RAOVLP,STZ(JK),RBOVLP
     45  PRINT *,'SU_OVLP: JK RAOVLP STZ RBOVLP:',JK,RAOVLP,STZ(JK),RBOVLP
    4646ENDDO 
    4747
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/suphec.F90

    r5159 r5160  
    190190!  VAH(JLEV)=ap(JLEV+1)ap(JLEV+1)
    191191!  VBH(JLEV)=bp(JLEV+1)
    192 print *,'SUPHEC: jlev ap bp',JLEV,ap(JLEV+1),bp(JLEV+1)
     192PRINT *,'SUPHEC: jlev ap bp',JLEV,ap(JLEV+1),bp(JLEV+1)
    193193   VAH(JLEV)=ap(NFLEVG+1-JLEV)
    194194   VBH(JLEV)=bp(NFLEVG+1-JLEV)
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/suphmf.F90

    r1990 r5160  
    9393
    9494IF (LHOOK) CALL DR_HOOK('SUPHMF',0,ZHOOK_HANDLE)
    95 print *,'SUPHMF: avant SU0PHY'
     95PRINT *,'SUPHMF: avant SU0PHY'
    9696CALL SU0PHY(KULOUT)
    97 print *,'SUPHMF: avant SUPHY0'
     97PRINT *,'SUPHMF: avant SUPHY0'
    9898CALL SUPHY0(KULOUT)
    99 print *,'SUPHMF: avant SUPHY1'
     99PRINT *,'SUPHMF: avant SUPHY1'
    100100CALL SUPHY1(KULOUT)
    101 print *,'SUPHMF: avant SUPHY2'
     101PRINT *,'SUPHMF: avant SUPHY2'
    102102CALL SUPHY2(KULOUT)
    103 print *,'SUPHMF: avant SUPHY3'
     103PRINT *,'SUPHMF: avant SUPHY3'
    104104CALL SUPHY3(KULOUT)
    105 print *,'SUPHMF: avant SUTOPH'
     105PRINT *,'SUPHMF: avant SUTOPH'
    106106CALL SUTOPH(KULOUT)
    107 print *,'SUPHMF: avant VAL923'
     107PRINT *,'SUPHMF: avant VAL923'
    108108
    109109CALL VAL923(LSOLV)
    110110
    111 print *,'SUPHMF: avant SUCAPE'
     111PRINT *,'SUPHMF: avant SUCAPE'
    112112CALL SUCAPE(KULOUT)
    113113
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/suphy.F90

    r5159 r5160  
    9797!              --------------------
    9898
    99 print *,'---- SUPHY: avant SUPHMF'
     99PRINT *,'---- SUPHY: avant SUPHMF'
    100100CALL SUPHMF(KULOUT)
    101101
    102 print *,'---- SUPHY: avant SUGFL'
     102PRINT *,'---- SUPHY: avant SUGFL'
    103103!SUGFL: Set up unified_treatment grid-point fields
    104104CALL SUGFL
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/sw1s.F90

    r5154 r5160  
    191191!   IKL = KLEV+1-JK
    192192!   DO JL = KIDIA,KFDIA
    193 !   print *,'Apres SWCLR,SWR RMU0 RMUE ',ZRMU0(JL,IKL),ZRMUE(JL,IKL)
     193!   PRINT *,'Apres SWCLR,SWR RMU0 RMUE ',ZRMU0(JL,IKL),ZRMUE(JL,IKL)
    194194!   ENDDO
    195195! ENDDO
     
    303303
    304304ELSEIF (NSW == 6) THEN
    305 !print *,'... dans SW1S: NSW=',NSW
     305!PRINT *,'... dans SW1S: NSW=',NSW
    306306
    307307!*         3.2   SIX SPECTRAL INTERVALS
     
    425425      PCU(JL,JK) = ZDIRF(JL) * RSUN(KNU)
    426426!WRITE(*,'("---> Dans SW1S:")')
    427 !print *,'===JL= ',jl
     427!PRINT *,'===JL= ',jl
    428428!WRITE(*,'("ZR1",10E12.5)') (ZR(JL,1))
    429429!WRITE(*,'("ZR2",10E12.5)') (ZR(JL,2))
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/swclr.F90

    r5154 r5160  
    229229! MPLFH : ZTRAY N'EST PAS INITIALISE !!!!! A REVOIR (MPL)
    230230      ZTRAY= PRAYL(JL) * PDSIG(JL,JK)
    231 !     print *,'>>>>>>> swclr: ZTRAY ',ZTRAY
     231!     PRINT *,'>>>>>>> swclr: ZTRAY ',ZTRAY
    232232      ZDENB = ZTRAY + PTAUAZ(JL,JK)*(1.0_JPRB-PPIZAZ(JL,JK)*ZFF)
    233233      ZRATIO=ZTRAY/ZDENB
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/swtt1.F90

    r1990 r5160  
    9191DO JA = 1,KABS
    9292  IA=KIND(JA)
    93 ! print *,'SWTT1: KNU', KNU
     93! PRINT *,'SWTT1: KNU', KNU
    9494  DO JL = KIDIA,KFDIA
    9595    ZU(JL) = PU(JL,JA)
     
    9898     & * ( APAD(KNU,IA,5) + ZU(JL) * (APAD(KNU,IA,6) + ZU(JL)&
    9999     & * ( APAD(KNU,IA,7) )))))) 
    100 !    print *,'SWTT1 ZU APAD',IA,ZU(JL),APAD(KNU,IA,1),APAD(KNU,IA,2),&
     100!    PRINT *,'SWTT1 ZU APAD',IA,ZU(JL),APAD(KNU,IA,1),APAD(KNU,IA,2),&
    101101!    &APAD(KNU,IA,3),APAD(KNU,IA,4),APAD(KNU,IA,5),APAD(KNU,IA,6),APAD(KNU,IA,7)
    102102
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/swu.F90

    r5154 r5160  
    180180    ZO175(JL) = ZN175(JL)
    181181    ZO190(JL) = ZN190(JL)
    182 !print *,'SWU: RTH2O RTDH2O RTUMG RTDUMG',RTH2O,RTDH2O,RTUMG,RTDUMG
    183 !print *,'SWU: RPNH ZDSH2O ZWH2O ZRTH',RPNH,ZDSH2O,ZWH2O,ZRTH
    184 !print *,'SWU: RPNU ZDSCO2 PCARDI ZRTU',RPNU,ZDSCO2,PCARDI,ZRTU
     182!PRINT *,'SWU: RTH2O RTDH2O RTUMG RTDUMG',RTH2O,RTDH2O,RTUMG,RTDUMG
     183!PRINT *,'SWU: RPNH ZDSH2O ZWH2O ZRTH',RPNH,ZDSH2O,ZWH2O,ZRTH
     184!PRINT *,'SWU: RPNU ZDSCO2 PCARDI ZRTU',RPNU,ZDSCO2,PCARDI,ZRTU
    185185
    186186!++MODIFCODE
  • LMDZ6/branches/Amaury_dev/libf/phylmd/rrtm/swuvo3.F90

    r5133 r5160  
    9090LLDEBUG=.FALSE.
    9191
    92 !print *,'Dans SWUVO3, N_VMASS= ',N_VMASS
     92!PRINT *,'Dans SWUVO3, N_VMASS= ',N_VMASS
    9393IF(N_VMASS > 0) THEN
    9494  JLEN=KFDIA-KIDIA+N_VMASS-MOD(KFDIA-KIDIA,N_VMASS)
Note: See TracChangeset for help on using the changeset viewer.