Changeset 1047 for trunk/LMDZ.MARS/libf/phymars/inifis.F
- Timestamp:
- Sep 23, 2013, 9:56:47 AM (11 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
trunk/LMDZ.MARS/libf/phymars/inifis.F
r1036 r1047 48 48 USE ioipsl_getincom, only : getin 49 49 use tracer_mod, only : nqmx, nuice_sed, ccn_factor 50 50 use comsoil_h, only: ini_comsoil_h 51 #ifdef MESOSCALE 52 use comsoil_h, only: volcapa !!MESOSCALE -- needed to fill volcapa 53 #endif 54 use comgeomfi_h, only: long, lati, area, totarea 55 use comdiurn_h, only: sinlat, coslat, sinlon, coslon 56 use surfdat_h, only: ini_surfdat_h, albedo_h2o_ice, inert_h2o_ice, 57 & frost_albedo_threshold 58 use comsaison_h, only: ini_comsaison_h 59 use slope_mod, only: ini_slope_mod 60 use dimradmars_mod, only: ini_dimradmars_mod 61 use yomaer_h,only: ini_yomaer_h, tauvis 62 use yomlw_h, only: ini_yomlw_h 63 use conc_mod, only: ini_conc_mod 51 64 IMPLICIT NONE 52 65 #include "dimensions.h" … … 54 67 #include "planete.h" 55 68 #include "comcstfi.h" 56 #include "comsaison.h"57 #include "comdiurn.h"58 #include "comgeomfi.h"69 !#include "comsaison.h" 70 !#include "comdiurn.h" 71 !#include "comgeomfi.h" 59 72 #include "callkeys.h" 60 #include "surfdat.h"61 #include "dimradmars.h"62 #include "yomaer.h"73 !#include "surfdat.h" 74 !#include "dimradmars.h" 75 !#include "yomaer.h" 63 76 #include "datafile.h" 64 #include "slope.h"77 !#include "slope.h" 65 78 #include "microphys.h" 66 79 !#include "tracer.h" 80 ! naerkind is set in scatterers.h (built when compiling with makegcm -s #) 81 #include"scatterers.h" 67 82 #ifdef MESOSCALE 68 #include "comsoil.h" !!MESOSCALE -- needed to fill volcapa83 !#include "comsoil.h" !!MESOSCALE -- needed to fill volcapa 69 84 #include "meso_inc/meso_inc_inifisvar.F" 70 85 #endif … … 107 122 ! The usual Tests 108 123 ! -------------- 109 IF (nlayer.NE.nlayermx) THEN110 PRINT*,'STOP in inifis'111 PRINT*,'Probleme de dimensions :'112 PRINT*,'nlayer = ',nlayer113 PRINT*,'nlayermx = ',nlayermx114 STOP115 ENDIF116 117 IF (ngrid.NE.ngridmx) THEN118 PRINT*,'STOP in inifis'119 PRINT*,'Probleme de dimensions :'120 PRINT*,'ngrid = ',ngrid121 PRINT*,'ngridmx = ',ngridmx122 STOP123 ENDIF124 ! IF (nlayer.NE.nlayermx) THEN 125 ! PRINT*,'STOP in inifis' 126 ! PRINT*,'Probleme de dimensions :' 127 ! PRINT*,'nlayer = ',nlayer 128 ! PRINT*,'nlayermx = ',nlayermx 129 ! STOP 130 ! ENDIF 131 132 ! IF (ngrid.NE.ngridmx) THEN 133 ! PRINT*,'STOP in inifis' 134 ! PRINT*,'Probleme de dimensions :' 135 ! PRINT*,'ngrid = ',ngrid 136 ! PRINT*,'ngridmx = ',ngridmx 137 ! STOP 138 ! ENDIF 124 139 125 140 ! -------------------------------------------------------------- … … 765 780 ! ------------------------ 766 781 767 ! in 'comgeomfi.h' 782 ! allocate "slope_mod" arrays 783 call ini_slope_mod(ngrid) 784 785 ! allocate "comsaison_h" arrays 786 call ini_comsaison_h(ngrid) 787 788 ! allocate "surfdat_h" arrays 789 call ini_surfdat_h(ngrid) 790 791 ! allocate "comgeomfi_h" arrays 792 allocate(lati(ngrid)) 793 allocate(long(ngrid)) 794 allocate(area(ngrid)) 795 796 ! fill "comgeomfi_h" data 768 797 CALL SCOPY(ngrid,plon,1,long,1) 769 798 CALL SCOPY(ngrid,plat,1,lati,1) 770 799 CALL SCOPY(ngrid,parea,1,area,1) 771 totarea=SSUM(ngridmx,area,1) 772 773 ! in 'comdiurn.h' 800 totarea=SSUM(ngrid,area,1) 801 802 ! allocate "comdiurn_h" data 803 allocate(sinlat(ngrid)) 804 allocate(coslat(ngrid)) 805 allocate(sinlon(ngrid)) 806 allocate(coslon(ngrid)) 807 808 ! fill "comdiurn_h" data 774 809 DO ig=1,ngrid 775 810 sinlat(ig)=sin(plat(ig)) … … 781 816 pi=2.*asin(1.) ! NB: pi is a common in comcstfi.h 782 817 783 ! managing the tracers, and tests: 784 ! ------------------------------- 785 ! Ehouarn: removed; as these tests are now done in initracer.F 786 ! if(tracer) then 787 ! 788 !! when photochem is used, nqchem_min is the rank 789 !! of the first chemical species 790 ! 791 !! Ehouarn: nqchem_min is now meaningless and no longer used 792 !! nqchem_min = 1 793 ! if (photochem .or. callthermos) then 794 ! chem = .true. 795 ! end if 796 ! 797 ! if (water .or. thermoswater) h2o = .true. 798 ! 799 !! TESTS 800 ! 801 ! print*,'inifis: TRACERS:' 802 ! write(*,*) " chem=",chem," h2o=",h2o 803 !! write(*,*) " doubleq=",doubleq 804 !! write(*,*) " dustbin=",dustbin 805 ! 806 ! if ((doubleq).and.(h2o).and. 807 ! $ (chem)) then 808 ! print*,' 2 dust tracers (doubleq)' 809 ! print*,' 1 water vapour tracer' 810 ! print*,' 1 water ice tracer' 811 ! print*,nq-4,' chemistry tracers' 812 ! endif 813 ! 814 ! if ((doubleq).and.(h2o).and. 815 ! $ .not.(chem)) then 816 ! print*,' 2 dust tracers (doubleq)' 817 ! print*,' 1 water vapour tracer' 818 ! print*,' 1 water ice tracer' 819 ! if (nq.LT.4) then 820 ! print*,'nq should be at least equal to' 821 ! print*,'4 with these options.' 822 ! stop 823 ! endif 824 ! endif 825 ! 826 ! if (.not.(doubleq).and.(h2o).and. 827 ! $ (chem)) then 828 ! if (dustbin.gt.0) then 829 ! print*,dustbin,' dust bins' 830 ! endif 831 ! print*,nq-2-dustbin,' chemistry tracers' 832 ! print*,' 1 water vapour tracer' 833 ! print*,' 1 water ice tracer' 834 ! endif 835 ! 836 ! if (.not.(doubleq).and.(h2o).and. 837 ! $ .not.(chem)) then 838 ! if (dustbin.gt.0) then 839 ! print*,dustbin,' dust bins' 840 ! endif 841 ! print*,' 1 water vapour tracer' 842 ! print*,' 1 water ice tracer' 843 ! if (nq.gt.(dustbin+2)) then 844 ! print*,'nq should be ',(dustbin+2), 845 ! $ ' with these options...' 846 ! print*,'(or check callphys.def)' 847 ! endif 848 ! if (nq.lt.(dustbin+2)) then 849 ! write(*,*) "inifis: nq.lt.(dustbin+2)" 850 ! stop 851 ! endif 852 ! endif 853 ! 854 ! endif ! of if (tracer) 855 ! 856 ! RETURN 818 ! allocate "comsoil_h" arrays 819 call ini_comsoil_h(ngrid) 820 821 ! set some variables in "dimradmars_mod" 822 call ini_dimradmars_mod(ngrid,nlayer) 823 824 ! allocate arrays in "yomaer_h" 825 call ini_yomaer_h 826 827 ! allocate arrays in "yomlw_h" 828 call ini_yomlw_h(ngrid) 829 830 ! allocate arrays in "conc_mod" 831 call ini_conc_mod(ngrid,nlayer) 832 857 833 END
Note: See TracChangeset
for help on using the changeset viewer.