Ignore:
Timestamp:
Nov 21, 2019, 4:43:45 PM (4 years ago)
Author:
lguez
Message:

Merge revisions 3427:3600 of trunk into branch Ocean_skin

Location:
LMDZ6/branches/Ocean_skin
Files:
2 edited

Legend:

Unmodified
Added
Removed
  • LMDZ6/branches/Ocean_skin

  • LMDZ6/branches/Ocean_skin/libf/phylmd/alpale_th.F90

    • Property svn:keywords set to Id
    r3209 r3605  
     1!
     2! $Id$
     3!
    14SUBROUTINE alpale_th ( dtime, lmax_th, t_seri, cell_area,  &
    25                       cin, s2, n2,  &
     
    6265 REAL umexp  ! expression of (1.-exp(-x))/x valid for all x, especially when x->0
    6366 REAL x
     67     CHARACTER (LEN=20) :: modname='alpale_th'
     68     CHARACTER (LEN=80) :: abort_message
     69     
    6470 umexp(x) = max(sign(1.,x-1.e-3),0.)*(1.-exp(-x))/max(x,1.e-3) + &
    6571            (1.-max(sign(1.,x-1.e-3),0.))*(1.-0.5*x*(1.-x/3.*(1.-0.25*x)))  !!! correct formula            (jyg)
     
    104110             !
    105111             IF (prt_level .GE. 10) THEN
    106                 print *,'cin, ale_bl_stat, alp_bl, alp_bl_stat ', &
     112                WRITE(lunout,*)'cin, ale_bl_stat, alp_bl, alp_bl_stat ', &
    107113                     cin, ale_bl_stat, alp_bl, alp_bl_stat
    108114             ENDIF
     
    122128             !
    123129             IF (prt_level .GE. 10) THEN
    124                 print *,'random_notrig, tau_trig ', &
     130                WRITE(lunout,*)'random_notrig, tau_trig ', &
    125131                     random_notrig, tau_trig
    126                 print *,'s_trig,s2,n2 ', &
     132                WRITE(lunout,*)'s_trig,s2,n2 ', &
    127133                     s_trig,s2,n2
    128134             ENDIF
     
    178184             !
    179185             IF (prt_level .GE. 10) THEN
    180                 print *,'proba_notrig, ale_bl_trig ', &
     186                WRITE(lunout,*)'proba_notrig, ale_bl_trig ', &
    181187                     proba_notrig, ale_bl_trig
    182188             ENDIF
     
    224230        !
    225231        IF (prt_level .GE. 10) THEN
    226            print *,'cin, ale_bl_stat, alp_bl_stat ', &
     232           WRITE(lunout,*)'cin, ale_bl_stat, alp_bl_stat ', &
    227233                cin, ale_bl_stat, alp_bl_stat
    228234        ENDIF
     
    253259        !
    254260        IF (prt_level .GE. 10) THEN
    255            print *,'random_notrig, tau_trig ', &
     261           WRITE(lunout,*)'random_notrig, tau_trig ', &
    256262                random_notrig, tau_trig
    257            print *,'s_trig,s2,n2 ', &
     263           WRITE(lunout,*)'s_trig,s2,n2 ', &
    258264                s_trig,s2,n2
    259265        ENDIF
     
    289295        !
    290296        IF (prt_level .GE. 10) THEN
    291            print *,'proba_notrig, ale_bl_trig ', &
     297           WRITE(lunout,*)'proba_notrig, ale_bl_trig ', &
    292298                proba_notrig, ale_bl_trig
    293299        ENDIF
     
    300306
    301307          IF (prt_level .GE. 10) THEN
    302              print *,'alpale_th: ale_bl_trig, alp_bl_stat, birth_rate ', &
     308             WRITE(lunout,*)'alpale_th: ale_bl_trig, alp_bl_stat, birth_rate ', &
    303309                      ale_bl_trig(1), alp_bl_stat(1), birth_rate(1)
    304310          ENDIF
     
    310316          if (iflag_coupl==2) then
    311317             IF (prt_level .GE. 10) THEN
    312                 print*,'Couplage Thermiques/Emanuel seulement si T<0'
     318                WRITE(lunout,*)'Couplage Thermiques/Emanuel seulement si T<0'
    313319             ENDIF
    314320             do i=1,klon
     
    317323                endif
    318324             enddo
    319     print *,'In order to run with iflag_coupl=2, you have to comment out the following stop'
    320              STOP
     325!    print *,'In order to run with iflag_coupl=2, you have to comment out the following stop'
     326!             STOP
     327             abort_message='In order to run with iflag_coupl=2, you have to comment out the following abort'
     328             CALL abort_physic(modname,abort_message,1)
    321329          endif
    322330   RETURN
Note: See TracChangeset for help on using the changeset viewer.