Ignore:
Timestamp:
04/03/13 12:05:12 (11 years ago)
Author:
sdubey
Message:
Added few new routines to read NC files and compute diagnostics to r145.
Few routines of dry physics including radiation module, surface process and convective adjustment in new routine phyparam.f90. dynetat to read start files for dynamics. check_conserve routine to compute conservation of quatities like mass, energy etc.etat0_heldsz.f90 for held-suarez test case initial conditions. new Key time_style=lmd or dcmip to use day_step, ndays like in LMDZ
File:
1 edited

Legend:

Unmodified
Added
Removed
  • codes/icosagcm/trunk/src/timeloop_gcm.f90

    r148 r149  
    1919  USE physics_mod 
    2020  USE mpipara 
     21  USE IOIPSL 
     22  USE maxicosa 
     23  USE check_conserve_mod 
    2124  USE trace 
    2225  USE transfert_mod 
     
    4346  REAL(rstd),POINTER :: dtheta_rhodz(:,:),dtheta_rhodzm1(:,:),dtheta_rhodzm2(:,:) 
    4447  REAL(rstd),POINTER :: hflux(:,:),wflux(:,:),hfluxt(:,:),wfluxt(:,:) 
    45  
    4648!  REAL(rstd) :: dt, run_length 
    4749  INTEGER :: ind 
     
    4951  CHARACTER(len=255) :: scheme_name 
    5052  LOGICAL :: fluxt_zero(ndomain) ! set to .TRUE. to start accumulating fluxes in time 
     53  CHARACTER(len=7) :: first  
     54  REAL(rstd),SAVE :: jD_cur, jH_cur 
     55  REAL(rstd),SAVE :: start_time 
    5156  LOGICAL, PARAMETER :: check=.FALSE. 
    5257!  INTEGER :: itaumax 
     
    8893  CALL allocate_field(f_wfluxt,field_t,type_real,llm+1) 
    8994 
     95!---------------------------------------------------- 
     96  IF (TRIM(time_style)=='lmd')  Then 
     97 
     98   day_step=180 
     99   CALL getin('day_step',day_step) 
     100 
     101   ndays=1 
     102   CALL getin('ndays',ndays) 
     103 
     104   dt = daysec/REAL(day_step) 
     105   itaumax = ndays*day_step 
     106 
     107   calend = 'earth_360d' 
     108   CALL getin('calend', calend) 
     109 
     110   day_ini = 0 
     111   CALL getin('day_ini',day_ini) 
     112 
     113   day_end = 0 
     114   CALL getin('day_end',day_end) 
     115 
     116   annee_ref = 1998 
     117   CALL getin('annee_ref',annee_ref) 
     118 
     119   start_time = 0 
     120   CALL getin('start_time',start_time)  
     121 
     122   write_period=0 
     123   CALL getin('write_period',write_period) 
     124       
     125   write_period=write_period/scale_factor 
     126   itau_out=FLOOR(write_period/dt) 
     127    
     128   PRINT *, 'Output frequency (scaled) set to ',write_period, ' : itau_out = ',itau_out  
     129 
     130  mois = 1 ; heure = 0. 
     131  call ymds2ju(annee_ref, mois, day_ref, heure, jD_ref) 
     132  jH_ref = jD_ref - int(jD_ref)  
     133  jD_ref = int(jD_ref)  
     134   
     135  CALL ioconf_startdate(INT(jD_ref),jH_ref)  
     136  write(*,*)'annee_ref, mois, day_ref, heure, jD_ref' 
     137  write(*,*)annee_ref, mois, day_ref, heure, jD_ref 
     138  write(*,*)"ndays,day_step,itaumax,dt======>" 
     139  write(*,*)ndays,day_step,itaumax,dt 
     140  call ju2ymds(jD_ref+jH_ref,an, mois, jour, heure) 
     141  write(*,*)'jD_ref+jH_ref,an, mois, jour, heure' 
     142  write(*,*)jD_ref+jH_ref,an, mois, jour, heure 
     143  day_end = day_ini + ndays  
     144 END IF  
     145!---------------------------------------------------- 
     146 
    90147  scheme_name='runge_kutta' 
    91148  CALL getin('scheme',scheme_name) 
     
    126183!  CALL allocate_field(f_dtheta_rhodzm1,field_t,type_real,llm) 
    127184!  CALL allocate_field(f_dtheta_rhodzm2,field_t,type_real,llm) 
    128  
    129185!  CALL allocate_field(f_theta,field_t,type_real,llm) 
    130186!  CALL allocate_field(f_dtheta,field_t,type_real,llm) 
     
    135191  CALL init_advect_tracer 
    136192  CALL init_physics 
    137  
    138     
    139   CALL etat0(f_ps,f_phis,f_theta_rhodz,f_u, f_q) 
     193!========================================= INITIALIZATION  
     194! CALL dynetat0(f_ps,f_phis,f_theta_rhodz,f_u,f_q) 
     195  CALL etat0(f_ps,f_phis,f_theta_rhodz,f_u,f_q) 
    140196  CALL writefield("phis",f_phis,once=.TRUE.) 
    141197  CALL transfert_request(f_q,req_i1)  
     
    158214     CALL compute_rhodz(.FALSE., ps, rhodz)    
    159215  END DO 
    160    
     216 
    161217  CALL transfert_request(f_phis,req_i0)  
     218  CALL transfert_request(f_phis,req_i1)  
    162219  CALL transfert_request(f_phis,req_i1)  
    163220 
     
    170227    ENDIF 
    171228     
    172     IF (is_mpi_root) PRINT *,"It No :",It,"   t :",dt*It 
    173229    IF (mod(it,itau_out)==0 ) THEN 
    174       CALL writefield("q",f_q) 
     230!      IF (is_mpi_root) PRINT *,"It No :",It,"   t :",dt*It 
    175231      CALL update_time_counter(dt*it) 
     232      CALL compute_conserve(f_ps,f_dps,f_u,f_theta_rhodz,f_phis,it)   
    176233    ENDIF 
    177      
    178     CALL guided(it*dt,f_ps,f_theta_rhodz,f_u,f_q) 
     234 
     235      CALL guided(it*dt,f_ps,f_theta_rhodz,f_u,f_q) 
    179236 
    180237    DO stage=1,nb_stage 
     
    189246       CASE (mlf) 
    190247          CALL  leapfrog_matsuno_scheme(stage) 
    191            
    192248          !      CASE ('leapfrog') 
    193           !        CALL leapfrog_scheme 
     249          !      CALL leapfrog_scheme 
    194250          ! 
    195251          !      CASE ('adam_bashforth') 
    196           !        CALL dissip(f_u,f_du,f_ps,f_phis, f_theta_rhodz,f_dtheta_rhodz) 
    197           !        CALL adam_bashforth_scheme 
     252          !      CALL dissip(f_u,f_du,f_ps,f_phis, f_theta_rhodz,f_dtheta_rhodz) 
     253          !      CALL adam_bashforth_scheme 
    198254       CASE DEFAULT 
    199255          STOP 
     
    208264    IF(MOD(it+1,itau_adv)==0) THEN 
    209265!       CALL transfert_request(f_wfluxt,req_i1) ! FIXME 
    210 !       CALL transfert_request(f_hfluxt,req_e1) ! FIXME 
     266!      CALL transfert_request(f_hfluxt,req_e1) ! FIXME 
    211267 
    212268       CALL advect_tracer(f_hfluxt,f_wfluxt,f_u, f_q,f_rhodz)  ! update q and rhodz after RK step 
     
    227283         END DO 
    228284       ENDIF 
    229  
    230285    END IF 
    231  
     286!---------------------------------------------------- 
     287  jD_cur = jD_ref + day_ini - day_ref + it/day_step 
     288  jH_cur = jH_ref + start_time + mod(it,day_step)/float(day_step) 
     289  jD_cur = jD_cur + int(jH_cur) 
     290  jH_cur = jH_cur - int(jH_cur) 
     291!       print*,"Just b4 phys" 
     292    CALL physics(it,jD_cur,jH_cur,f_phis, f_ps, f_theta_rhodz, f_u, f_q) 
     293!---------------------------------------------------- 
    232294!    CALL physics(it,f_phis, f_ps, f_theta_rhodz, f_u, f_q) 
    233295    ENDDO 
     
    493555          DO i=ii_begin-dd,ii_end+dd 
    494556             ij=(j-1)*iim+i 
    495              m = ( ap(l) - ap(l+1) + (bp(l)-bp(l+1))*ps(ij) )/g  
     557             m = ( ap(l) - ap(l+1) + (bp(l)-bp(l+1))*ps(ij) )/g 
    496558             IF(comp) THEN 
    497559                rhodz(ij,l) = m 
     
    508570          STOP 
    509571       ELSE 
    510 !          PRINT *, 'No discrepancy between ps and rhodz detected' 
     572          PRINT *, 'No discrepancy between ps and rhodz detected' 
    511573       END IF 
    512574    END IF 
Note: See TracChangeset for help on using the changeset viewer.