/[lmdze]/trunk/libf/dyn3d/etat0.f90
ViewVC logotype

Diff of /trunk/libf/dyn3d/etat0.f90

Parent Directory Parent Directory | Revision Log Revision Log | View Patch Patch

revision 32 by guez, Tue Apr 6 17:52:58 2010 UTC revision 39 by guez, Tue Jan 25 15:11:05 2011 UTC
# Line 20  contains Line 20  contains
20      ! This subroutine creates "mask".      ! This subroutine creates "mask".
21    
22      use caldyn0_m, only: caldyn0      use caldyn0_m, only: caldyn0
23      use comconst, only: dtvr, daysec, cpp, kappa, pi      use comconst, only: dtvr, daysec, cpp, kappa
24      use comgeom, only: rlatu, rlonv, rlonu, rlatv, aire_2d, apoln, apols, &      use comgeom, only: rlatu, rlonv, rlonu, rlatv, aire_2d, apoln, apols, &
25           cu_2d, cv_2d           cu_2d, cv_2d
26      use comvert, only: ap, bp, preff, pa      use comvert, only: ap, bp, preff, pa
# Line 31  contains Line 31  contains
31      use dynredem0_m, only: dynredem0      use dynredem0_m, only: dynredem0
32      use dynredem1_m, only: dynredem1      use dynredem1_m, only: dynredem1
33      use exner_hyb_m, only: exner_hyb      use exner_hyb_m, only: exner_hyb
34        USE flincom, only: flinclo, flinopen_nozoom, flininfo
35        use flinget_m, only: flinget
36      use grid_atob, only: grille_m      use grid_atob, only: grille_m
37      use grid_change, only: init_dyn_phy, dyn_phy      use grid_change, only: init_dyn_phy, dyn_phy
38        use histcom, only: histclo
39      use indicesol, only: is_oce, is_sic, is_ter, is_lic, epsfra      use indicesol, only: is_oce, is_sic, is_ter, is_lic, epsfra
40      use iniadvtrac_m, only: iniadvtrac      use iniadvtrac_m, only: iniadvtrac
41      use inidissip_m, only: inidissip      use inidissip_m, only: inidissip
42      use inigeom_m, only: inigeom      use inigeom_m, only: inigeom
43      USE flincom, only: flinclo, flinopen_nozoom, flininfo      use nr_util, only: pi
     use flinget_m, only: flinget  
     use histcom, only: histclo  
44      use paramet_m, only: ip1jm, ip1jmp1      use paramet_m, only: ip1jm, ip1jmp1
45      use phyredem_m, only: phyredem      use phyredem_m, only: phyredem
46      use pressure_var, only: pls, p3d      use pressure_var, only: pls, p3d
# Line 114  contains Line 115  contains
115    
116      print *, "Call sequence information: etat0"      print *, "Call sequence information: etat0"
117    
     ! Construct a grid:  
   
118      dtvr = daysec / real(day_step)      dtvr = daysec / real(day_step)
119      print *, 'dtvr = ', dtvr      print *, 'dtvr = ', dtvr
120    
121        ! Construct a grid:
122    
123      pa = 5e4      pa = 5e4
124      CALL iniconst      CALL iniconst
125      CALL inigeom      CALL inigeom
# Line 147  contains Line 148  contains
148      CALL exner_hyb(psol, p3d, pks, pk)      CALL exner_hyb(psol, p3d, pks, pk)
149      IF (MINVAL(pk) == MAXVAL(pk)) stop '"pk" should not be constant'      IF (MINVAL(pk) == MAXVAL(pk)) stop '"pk" should not be constant'
150    
151      pls(:, :, :) = preff * (pk(:, :, :) / cpp)**(1. / kappa)      pls = preff * (pk / cpp)**(1. / kappa)
152      PRINT *, "minval(pls(:, :, :)) = ", minval(pls(:, :, :))      PRINT *, "minval(pls) = ", minval(pls)
153      print *, "maxval(pls(:, :, :)) = ", maxval(pls(:, :, :))      print *, "maxval(pls) = ", maxval(pls)
154    
155      call start_inter_3d('U', rlonv, rlatv, pls, uvent)      call start_inter_3d('U', rlonv, rlatv, pls, uvent)
156      forall (l = 1: llm) uvent(:iim, :, l) = uvent(:iim, :, l) * cu_2d(:iim, :)      forall (l = 1: llm) uvent(:iim, :, l) = uvent(:iim, :, l) * cu_2d(:iim, :)
# Line 160  contains Line 161  contains
161      vvent(iim + 1, :, :) = vvent(1, :, :)      vvent(iim + 1, :, :) = vvent(1, :, :)
162    
163      call start_inter_3d('TEMP', rlonu, rlatv, pls, t3d)      call start_inter_3d('TEMP', rlonu, rlatv, pls, t3d)
164      PRINT *,  'minval(t3d(:, :, :)) = ', minval(t3d(:, :, :))      PRINT *,  'minval(t3d) = ', minval(t3d)
165      print *, "maxval(t3d(:, :, :)) = ", maxval(t3d(:, :, :))      print *, "maxval(t3d) = ", maxval(t3d)
166    
167      tpot(:iim, :, :) = t3d(:iim, :, :) * cpp / pk(:iim, :, :)      tpot(:iim, :, :) = t3d(:iim, :, :) * cpp / pk(:iim, :, :)
168      tpot(iim + 1, :, :) = tpot(1, :, :)      tpot(iim + 1, :, :) = tpot(1, :, :)
# Line 172  contains Line 173  contains
173      ENDDO      ENDDO
174    
175      ! Calcul de l'humidité ŕ saturation :      ! Calcul de l'humidité ŕ saturation :
176      qsat(:, :, :) = q_sat(t3d, pls)      qsat = q_sat(t3d, pls)
177      PRINT *, "minval(qsat(:, :, :)) = ", minval(qsat(:, :, :))      PRINT *, "minval(qsat) = ", minval(qsat)
178      print *, "maxval(qsat(:, :, :)) = ", maxval(qsat(:, :, :))      print *, "maxval(qsat) = ", maxval(qsat)
179      IF (MINVAL(qsat) == MAXVAL(qsat)) stop '"qsat" should not be constant'      IF (MINVAL(qsat) == MAXVAL(qsat)) stop '"qsat" should not be constant'
180    
181      ! Water vapor:      ! Water vapor:

Legend:
Removed from v.32  
changed lines
  Added in v.39

  ViewVC Help
Powered by ViewVC 1.1.21