Changeset 9 for trunk/SOURCES


Ignore:
Timestamp:
02/12/15 11:42:12 (9 years ago)
Author:
dumas
Message:

Mise en place de Hemin-40 avec nouveaux module climat : climat_forcage_mois_mod.f90, ablation_mod.f90, pdd_declar_mod.f90. Suppression de l'appel à lect-clim-act-hemin40_mod.f90

Location:
trunk/SOURCES
Files:
8 added
13 edited

Legend:

Unmodified
Added
Removed
  • trunk/SOURCES/3D-physique-gen_mod.f90

    r4 r9  
    4747  !integer ::  NYEAR                    !< number of months in 1 year, st. dev. for temp *) 
    4848  integer ::  NTMAX                     !<  
    49   integer ::  NDAY                      !<  
     49!  integer ::  NDAY                      !<  
    5050  integer ::  NP                        !<  
    5151  real ::  NDISP                        !< sortie courte (temps) 
     
    122122  ! real ::  PY                           ! ct for PDD calculation 
    123123  real ::  PYY                          !<  
    124   real ::  PSOLID                       !< temp limit between liquid and solid precip 
     124!  real ::  PSOLID                       !< temp limit between liquid and solid precip 
    125125  ! real ::  PDDCT                        ! ct for PDD calculation      
    126126  real ::  PDSI                         !<  
     
    141141  real ::  SURF                         !<  
    142142  real ::  STEP                         !<  
    143   real ::  SIF                          !<  
    144   real ::  SUMM                         !<  
     143!  real ::  SIF                          !<  
     144!  real ::  SUMM                         !<  
    145145  real ::  SIMAX                        !<  
    146146  real ::  SPHI                         !<  
    147   real ::  TEMPGRAD                     !< atmospheric temperature gradient (annual) 
    148   real ::  TEMPGRJUL                    !< atmospheric temperature gradient (july) 
     147!  real ::  TEMPGRAD                     !< atmospheric temperature gradient (annual) 
     148!  real ::  TEMPGRJUL                    !< atmospheric temperature gradient (july) 
    149149  real (kind=kind(0.d0)) ::  TIME       !< temps : en double precision 
    150150  real ::  TAFOR                        !< temperature forcing : annual 
    151151  real ::  TJFOR                        !< temperature forcing : july 
    152   real ::  TEMP                         !<  
     152!  real ::  TEMP                         !<  
    153153  real ::  TESTDIAG                     !< for time step calculation (icethick) 
    154154  real ::  V_limit                      !< vitesse maxi (limitateur de flux pour conserv masse) 
     
    210210  real,dimension(NZ) :: UZCOMPLETE      !<  pour sorties eismint (vitesse vert. non reduite) 
    211211 
    212   real,dimension(365) :: TT             !< air temperature yearly cycle, for PDD 
     212!  real,dimension(365) :: TT             !< air temperature yearly cycle, for PDD 
    213213  
    214214  real,dimension(NX) :: FLUX            !<  
     
    338338  real,dimension(nx,ny) :: TJULY        !< Ground air temperature July 
    339339  real,dimension(nx,ny) :: TANN         !< Ground air temperature annual 
     340  real,dimension(nx,ny,12) :: Tmois        !< Ground air temperature monthly 
    340341  real,dimension(nx,ny) :: TSHELF       !< temperature des shelfs pour viscosite 
    341342  real,dimension(nx,ny) :: TJ0          !< initial air temperature at sea level July 
     
    366367  real,dimension(nx,ny) :: XLONG        !< longitude 
    367368  real,dimension(nx,ny) :: YLAT         !< latitude 
    368   real,dimension(nx,ny) :: ZS           !< surface topography above sea level 
     369  real,dimension(nx,ny) :: xcc          ! grille Xkm 
     370  real,dimension(nx,ny) :: ycc          ! grille Ykm 
     371!  real,dimension(nx,ny) :: ZS           !< surface topography above sea level 
    369372  real,dimension(nx,ny) :: ETABAR       !<  
    370373  real,dimension(nx,ny) :: BSOC         !< altitude (ou bathymetrie) du socle 'o' 
  • trunk/SOURCES/Fichiers-parametres/Makefile.tof-lsce3130.inc

    r5 r9  
    3636IFORT= ifort 
    3737 
    38 ARITHM    = -O2 -fp-model precise  -heap-arrays -traceback # -traceback   -CB  -g  # options pour une meilleure arithmetique 
     38ARITHM    = -O2 -fp-model precise  -heap-arrays -traceback -diag-disable warn # -traceback   -CB  -g  # options pour une meilleure arithmetique 
    3939                                                                      # (normalement reproductible) 
    4040#ARITHM    =  -fp-model precise -warn all -CU -CA # options pour une meilleure arithmetique (normalement reproductible) 
  • trunk/SOURCES/Hemin40_files/fake-routines-hemin40_mod.f90

    r4 r9  
    1616 
    1717use module3d_phy 
    18 use deform_declar 
    1918implicit none 
    2019 
     
    3938end subroutine track_change_T 
    4039 
     40!____________________________________________________ 
     41subroutine time_step_recul 
     42 
     43if (itracebug.eq.1)  call tracebug(' Entree dans routine fake time_step_recul') 
     44! quand on n'utilise pas le recul 
     45end subroutine time_step_recul 
     46 
    4147end module fake_nor 
    4248! 
  • trunk/SOURCES/Hemin40_files/lect-hemin40_mod.f90

    r4 r9  
    1 !> \file lect-hemin40_mod.f90 
    2 !! Module de lecture de la topography a 40 km 
    3 !< 
    4  
    5 !> \namespace  dragging_calc_beta 
    6 !! Module de lecture de la topography a 40 km 
    7 !! \author ... 
    8 !! \date ... 
    9 !! @note Used module 
    10 !! @note   - use module3D_phy 
    11 !< 
    12  
    131module lect_topo_hemin40 
    142 
    153  use module3D_phy 
    164   
    17     character(len=35) :: FILE1 ! CHARACTER(LEN=30) :: FILE1, FILE2,  FILE3 
    18     character(len=35) :: FILE2 
     5    character(len=50) :: FILE1 ! CHARACTER(LEN=30) :: FILE1, FILE2,  FILE3 
     6    character(len=50) :: FILE2 
    197    character(len=80) :: filin 
    20 real,dimension(nx,ny) ::  xcc , ycc        !< coordeonnes en m 
    21 real, dimension(nx,ny,5) :: bidon          !< pour l'appel a courbure 
     8    real, dimension(nx,ny,5) :: bidon          ! pour l'appel a courbure 
    229 
    2310contains 
     
    2512subroutine input_topo 
    2613 
     14namelist/topo_file/file1,file2 
     15rewind(num_param)        ! pour revenir au debut du fichier param_list.dat 
     16read(num_param,topo_file) 
     17! formats pour les ecritures dans 42 
     18428 format(A) 
     19write(num_rep_42,428)'!___________________________________________________________'  
     20write(num_rep_42,428) '&topo_file                                  ! nom du bloc ' 
     21write(num_rep_42,*) 
     22write(num_rep_42,*) 'file1 = ', file1 
     23write(num_rep_42,*) 'file2 = ', file2 
     24write(num_rep_42,*)'/'  
     25write(num_rep_42,428) '! file1 : topo de depart' 
     26write(num_rep_42,428) '! file2 : topo de reference'              
     27write(num_rep_42,*) 
     28 
    2729!====================================== La reponse est 42 =========== 
    28  write(42,*) 
    29  write(42,*)' Fichiers en entree' 
    30  write(42,*)'----------------------' 
     30! write(42,*) 
     31! write(42,*)' Fichiers en entree' 
     32! write(42,*)'----------------------' 
    3133!====================================================================  
    3234 
    33  
    34       file1=TRIM(DIRNAMEINP)//'topo-21k.g40'     ! topo LGM ICE_5G (1=topo de depart) 
     35! dans param : 
     36!      file1=TRIM(DIRNAMEINP)//'topo-21k.g40'     ! topo LGM ICE_5G (1=topo de depart) 
    3537!      file1=TRIM(DIRNAMEINP)//'hemin2.g40' 
    36       file2=TRIM(DIRNAMEINP)//'hemin2.g40'       ! topo actuelle 
    37       write(42,*) 'topo de depart', file1 
    38       write(42,*) 'topo reference', file2 
     38!      file2=TRIM(DIRNAMEINP)//'hemin2.g40'       ! topo actuelle 
     39!      write(42,*) 'topo de depart', file1 
     40!      write(42,*) 'topo reference', file2 
    3941 
    4042       
     
    4547!     lecture de la topo actuelle 
    4648!     --------------------------- 
    47      open (20,file=file2) 
     49     open (20,file=TRIM(DIRNAMEINP)//file2,status='old') 
    4850        
    4951     read(20,'(A80)') TITRE 
     
    5254         do J=1,ny  
    5355          do I=1,nx 
    54              read (20,*)  S0(I,J),H0(I,J),Bsoc0(I,J) 
     56             read (20,*)  S0(I,J),H0(I,J),BSOC0(I,J) 
    5557             S0(i,j)=max(S0(i,j),0.) 
    5658          end do 
     
    6163!     lecture de la topo de depart 
    6264!     --------------------------- 
    63      open (20,file=file1) 
     65     open (20,file=TRIM(DIRNAMEINP)//file1,status='old') 
    6466!         open (20,file='../INPUT-DATA/hemin.g50') 
    6567     read(20,'(A80)') TITRE 
     
    7274        end do 
    7375     close(20) 
    74       
     76 
     77! calcul des courbures du socle 
     78 
     79     call courbure(nx,ny,dx,Bsoc,bidon(:,:,1),bidon(:,:,2),bidon(:,:,3), & 
     80          bidon(:,:,4),socle_cry,bidon(:,:,5)) 
     81     socle_cry(:,:)=socle_cry(:,:)*dx*dx 
     82 
    7583! lecture des coordonnées geographiques 
    7684 
     
    8088! les longitudes sont comprises entre -180 et +180 (negative a l'Ouest de 
    8189! Greenwich et positive a l'Est) 
    82        open(unit=2004,file=filin,iostat=ios) 
    83            do k=1,nx*ny 
    84            read(2004,*) i,j,XCC(i,j),YCC(i,j),XLONG(i,j),YLAT(i,j) 
    85            enddo 
    86        close(2004) 
    87 write(42,*) 'fichier grille: ', filin 
     90    open(unit=2004,file=filin,iostat=ios) 
     91    do k=1,nx*ny 
     92       read(2004,*) i,j,XCC(i,j),YCC(i,j),XLONG(i,j),YLAT(i,j) 
     93    enddo 
     94    close(2004) 
     95    write(42,*) 'fichier grille: ', filin 
    8896               
    89       xmin=xcc(1,1)/1000. 
    90       ymin=ycc(1,1)/1000. 
    91       xmax=xcc(nx,ny)/1000. 
    92       ymax=ycc(nx,ny)/1000. 
     97    xmin=xcc(1,1)/1000. 
     98    ymin=ycc(1,1)/1000. 
     99    xmax=xcc(nx,ny)/1000. 
     100    ymax=ycc(nx,ny)/1000. 
     101                          
     102! lecture du flux geothermique de Shapiro 
     103    open(88,file=TRIM(DIRNAMEINP)//'ijphi_hemin40.dat') 
    93104 
    94 ! appel a la routine de calcul de courbure 
    95       call courbure(nx,ny,dx,Bsoc,bidon(:,:,1),bidon(:,:,2),bidon(:,:,3), & 
    96            bidon(:,:,4),socle_cry,bidon(:,:,5)) 
     105    write(42,*) 'flux geothermique Shapiro : ',TRIM(DIRNAMEINP)//'ijphi_hemin40.dat' 
    97106 
    98       socle_cry(:,:)=socle_cry(:,:)*dx*dx 
    99  
    100  
    101                         
    102 ! lecture du flux geothermique de Shapiro 
    103       open(88,file=TRIM(DIRNAMEINP)//'ijphi_hemin40.dat') 
    104  
    105       write(42,*) 'flux geothermique Shapiro : ',TRIM(DIRNAMEINP)//'ijphi_hemin40.dat' 
    106  
    107       do k=1,nx*ny 
    108          read(88,*) i,j,ghf(i,j) 
     107    do k=1,nx*ny 
     108       read(88,*) i,j,ghf(i,j) 
    109109!        print*, i,j,ghf(i,j) 
    110       end do 
    111       close(88) 
     110    end do 
     111    close(88) 
    112112! pour passer les flux des mW/m2 au J/m2/an       
    113       ghf(:,:)=-SECYEAR/1000.*ghf(:,:) 
     113    ghf(:,:)=-SECYEAR/1000.*ghf(:,:) 
    114114!     write(42,*) 'flux geothermique fixe : 55 mW/m2'  
    115115!     ghf(:,:)=-SECYEAR/1000.*55. !B6norcg2 
    116116 
    117 print*,'lect topo' 
    118 print*,'shb',S(101,91),H(101,91),B(101,91) 
    119 print*,'shb0',S0(101,91),H0(101,91),Bsoc0(101,91) 
     117! print*,'lect topo' 
     118! print*,'shb',S(101,91),H(101,91),B(101,91) 
     119! print*,'shb0',S0(101,91),H0(101,91),BSOC0(101,91) 
    120120!    Initialisation du Masque 
    121121!------------------------------------------------ 
  • trunk/SOURCES/Hemin40_files/module_choix-hemin40-0.4.f90

    r4 r9  
    4040 
    4141!--------------Lecture climat ref ------------------ 
     42! Le climat de ref si necessaire est maintenant lu par le module de climat directement 
    4243!use lect_clim_act_anteis 
    43  use lect_clim_act_hemin40 ! pour l'hemisphere nord et l'eurasie 
     44!use lect_clim_act_hemin40 ! pour l'hemisphere nord et l'eurasie 
    4445! use  climat_heino 
    4546 
    4647!--------------Lecture climat forcage--------------- 
    4748 
    48 !use climat_perturb_mod 
    49  use climat_forcage_mod 
     49!use climat_perturb_mod ! pour simule climat equilibre type Loveclim 
     50!use climat_forcage_stat_mois_mod  ! climat constant mensuel GCMs 
     51!use climat_forcage_mod ! pour cycle force GCM avec index 
     52use climat_forcage_mois_mod ! forcage mensuel GCM 1 Snapshot 
     53! use climat_forcage_insolation_mod ! methode JB multi-snapshots mensuelle mais pour un etat stationnaire avec correction topo GCM => GRISLI 
    5054!use climat_synthes_mod 
    5155!use climat_profil_mod 
    5256!use climat_regions_delta 
    5357 
     58use ablation_mod ! calcul de l'ablation (PDD ou autre methode) 
     59 
    5460! pas de lacs proglaciaires 
    5561use no_lakes 
    5662 
     63! suivi des traceurs ou pas ? 
     64!use tracer_mod  ! probablement pas compatible avec Hemin-40 actuellement 
     65use notracer_mod 
     66 
    5767!--------------Choix isostasie---------------------- 
    58  use isostasie_mod  ! module permettant de calculer la deflexion isostasique 
    59 ! USE NOISOSTASIE_MOD ! module pour ne pas avoir d'isostasie 
     68use isostasie_mod    ! module permettant de calculer la deflexion isostasique 
     69!use noisostasie_mod ! module pour ne pas avoir d'isostasie 
    6070 
    6171 
    6272!--------------Module Physique--------------------- 
    63 use deformation_mod  ! module concernant les lois de deformation 
     73!use deformation_mod         ! module concernant les lois de deformation 
     74use deformation_mod_2lois   ! module concernant les lois de deformation 
    6475 
    6576!--------------Module propritete thermique de la glace 
    66 use  prop_thermiques_ice 
     77use prop_thermiques_ice 
    6778! use prop_therm_ice_heino 
    6879 
     
    7182 
    7283! sliding- dragging 
    73 ! use module sliding_vitbal 
     84!use module sliding_vitbal 
    7485use sliding_Bindschadler 
    75 ! use sliding_dragging_heino    ! loi de glissement heino : mis dans diffusiv :  
     86!use sliding_dragging_heino    ! loi de glissement heino : mis dans diffusiv :  
    7687 
    7788 
    7889!use dragging_vitbil 
    79 ! use dragging_hwatstream 
     90!use dragging_hwatstream 
    8091use dragging_hwat_contmaj 
    81  
    8292!use dragging_hwat_cont 
    8393 
    84 !use dragging_hwat_contmaj 
     94!------------ spinup ----------------------------------- 
     95use no_spinup           ! spinup=0 
     96!use spinup_vitbil         ! plusieurs variantes de spinup : inclue le dragging 
     97                          ! enlever le use dragging dans ce cas là 
    8598 
    8699! use eq_elliptique_mod ! ancienne version (remplimat-5) 
     
    93106! choix resolution de la conservation de la masse 
    94107!----------------------------------------------- 
    95 use equat_adv_diff_2D          ! conservation masse avec advection-diffusion 
     108!use equat_adv_diff_2D          ! conservation masse avec advection-diffusion 
     109use equat_adv_diff_2D_vect      ! le vecteur est maintenant dans l'appel 
    96110 
    97111 
    98112!--------------Fusion basale------------------------ 
    99113!use bmelt_ant_regions ! pour l'Antarctique avec régions 
    100  use bmelt_nor_regions ! pour le nord avec régions 
     114use bmelt_nor_regions ! pour le nord avec régions 
    101115!use bmelt_nor_depth   ! pour le nord avec profondeur d'eau 
    102116 
     
    105119! use fake_heino 
    106120! use fake_ant 
    107  use fake_nor 
     121use fake_nor 
    108122!-------------- Outputs----------------------------- 
    109123! 
     
    113127 
    114128!-----Suivi temporel 
    115  use output_hemin40_mod 
     129use output_hemin40_mod 
    116130! use output_antarcti_mod 
    117131! use output_heino 
  • trunk/SOURCES/Makefile.grisli.inc

    r7 r9  
    3737# modules climats : doivent etre compatibles avec les modules choix 
    3838# il faut choisir un des deux ou un specifique a une geometrie. 
     39 
     40# module de forcage climatique C. Dumas 
     41mod_clim_tof = climat_forcage_mois_mod.o pdd_declar_mod.o ablation_mod.o 
    3942 
    4043# methode forcage basee sur des snapshots climats 
     
    6972        out_profile_mod.o printtable_mod.o mix-SIA-L1_mod.o \ 
    7073        relaxation_mod-0.3.o relaxation_water_mod-0.4.o relaxation_water_diffusion.o \ 
    71         prescribe-H_mod.o       \ 
     74        prescribe-H-i2s_mod.o  \ 
    7275        resol_adv_diff_2D-sept2009.o  \ 
    7376        conserv-mass-adv-diff_sept2009_mod.o  \ 
     
    105108mod_tracers = tracer_vars_mod.o tracer_mod.o notracer_mod.o \ 
    106109        interpolate_tracer.o celltest_tracer.o   
     110# no_tracer a part pour eviter pb avec climat_perturb => voir avec Cat 
     111mod_no_tracers = tracer_vars_mod.o notracer_mod.o 
     112 
    107113 
    108114Proto_recul = proto_declar_3D_grisli_mod.o \ 
     
    190196 
    191197Liste_hemin40 = output_hemin40_mod-0.4.o \ 
    192         lect-clim-act-hemin40_mod.o lect-hemin40_mod.o  \ 
    193         climat-forcage_mod-0.4.o climat-perturb_mod-0.4.o \ 
     198        lect-hemin40_mod.o  \ 
    194199        bmelt-hemin40-regions_mod.o bmelt-hemin40-depth_mod.o \ 
    195200        fake-routines-hemin40_mod.o  module_choix-hemin40-0.4.o \ 
     
    595600# modules de climat 
    596601# --------------------------- 
     602# nouveaux modules climat C. Dumas Fev 2015 
     603climat_forcage_mois_mod.o : climat_forcage_mois_mod.f90 
     604        $(FT) climat_forcage_mois_mod.f90 
     605 
     606pdd_declar_mod.o : pdd_declar_mod.f90 
     607        $(FT) pdd_declar_mod.f90 
     608 
     609ablation_mod.o : ablation_mod.f90 
     610        $(FT) ablation_mod.f90 
     611 
     612 
     613##### anciens modules 
    597614climat-forcage_mod-0.4.o : climat-forcage_mod-0.4.f90  
    598615        $(FT) climat-forcage_mod-0.4.f90 
     
    13361353readinput.o: readinput.f90  
    13371354        $(F_NETCDF) readinput.f90  
     1355 
    13381356interface_input.o: interface_input.f90 
    13391357        $(FT) interface_input.f90 
     
    14861504        $(routine_elliptiques) $(NCDF_LIB)  $(MKL_LIB) 
    14871505 
    1488  
     1506Hemin-40 : $(Dim_hemin40) $(mod_dim_communs) \ 
     1507        $(toy_recul)  \ 
     1508        $(mod_communs) \ 
     1509        $(mod_clim_tof) \ 
     1510        $(mod_no_tracers) \ 
     1511        $(mod_ell) $(Liste_hemin40) \ 
     1512        $(mod_post_geo) \ 
     1513        $(diagnoshelf) \ 
     1514        $(Liste_Netcdf) \ 
     1515        $(routines_communes) steps_time_loop.o \ 
     1516        $(routine_elliptiques) 
     1517 
     1518        $(LK) -o  ../bin/Hemin-40 \ 
     1519        $(Dim_hemin40) $(mod_dim_communs) \ 
     1520        $(toy_recul)  \ 
     1521        $(mod_communs) \ 
     1522        $(mod_clim_tof) \ 
     1523        $(mod_no_tracers) \ 
     1524        $(mod_ell) $(Liste_hemin40) \ 
     1525        $(mod_post_geo) \ 
     1526        $(diagnoshelf) \ 
     1527        $(Liste_Netcdf) \ 
     1528        $(routines_communes) steps_time_loop.o \ 
     1529        $(routine_elliptiques) $(NCDF_LIB)  $(MKL_LIB) 
    14891530 
    14901531 
     
    14981539        $(routines_communes) $(routine_elliptiques) $(NCDF_LIB) $(MKL_LIB) 
    14991540 
    1500 Hemin-40 : $(Dim_hemin40) $(mod_dim_communs) $(mod_communs)  $(mod_ell)  $(Liste_hemin40) \ 
    1501         $(diagnoshelf) $(Liste_Netcdf) \ 
    1502         $(routines_communes) $(routine_elliptiques)   
    1503  
    1504         $(LK) -o  ../bin/Hemin-40  $(Dim_hemin40) $(mod_dim_communs) $(mod_communs) \ 
    1505         $(mod_ell)  $(Liste_hemin40) \ 
    1506         $(diagnoshelf) $(Liste_Netcdf) \ 
    1507         $(routines_communes) $(routine_elliptiques) $(NCDF_LIB)  $(MKL_LIB) 
     1541#Hemin-40 : $(Dim_hemin40) $(mod_dim_communs) $(mod_communs)  $(mod_ell)  $(Liste_hemin40) \ 
     1542#       $(diagnoshelf) $(Liste_Netcdf) \ 
     1543#       $(routines_communes) $(routine_elliptiques)   
     1544 
     1545#       $(LK) -o  ../bin/Hemin-40  $(Dim_hemin40) $(mod_dim_communs) $(mod_communs) \ 
     1546#       $(mod_ell)  $(Liste_hemin40) \ 
     1547#       $(diagnoshelf) $(Liste_Netcdf) \ 
     1548#       $(routines_communes) $(routine_elliptiques) $(NCDF_LIB)  $(MKL_LIB) 
    15081549 
    15091550Heminord : $(Liste_heminord) $(Liste_commune) $(Liste_BLAS) 
  • trunk/SOURCES/dragging_hwat_contmaj_mod.f90

    r4 r9  
    4343real :: tob_ile    ! pour les iles 
    4444real :: cry_lim=50.  ! courbure limite pour le suivi des fleuves 
     45 
     46 
     47real, dimension(nx,ny) :: Vcol_x           !< uniquement pour compatibilite avec spinup cat 
     48real, dimension(nx,ny) :: Vcol_y           !< uniquement pour compatibilite avec spinup cat 
     49real, dimension(nx,ny) :: Vsl_x            !< uniquement pour compatibilite avec spinup cat 
     50real, dimension(nx,ny) :: Vsl_y            !< uniquement pour compatibilite avec spinup cat 
     51logical :: corr_def = .false.              !< for deformation correction, pour compatibilite beta 
     52 
    4553contains 
    4654!------------------------------------------------------------------------------- 
  • trunk/SOURCES/initial-0.3.f90

    r4 r9  
    4343  !------------------------------------------------------ 
    4444  ! initialisation du climat  (reference et forcage) 
    45   call  input_climat_ref()  ! Le climat de reference 
    46   call  init_forclim        ! les parametres du forcage 
    47   call  input_clim()        ! Les fichiers de forcage 
    48   call  init_ablation 
     45!cdc  call input_climat_ref()  ! Le climat de reference 
     46  call init_forclim        ! parametres du forcage 
     47  call input_clim          ! lecture fichiers de forcage 
     48  call init_ablation       ! parametres du calcul de l'ablation 
     49  call init_ablation 
    4950  !------------------------------------------------------------------------------------- 
    5051 
  • trunk/SOURCES/initial-phy-2-job.f90

    r4 r9  
    190190  SEALEVEL=0.0 
    191191 
    192  
    193   !     temp limit between liquid and solid precip 
    194   PSOLID=2. 
    195  
    196  
    197192  SECYEAR=365.*24.*3600. 
    198193  secyear= 31556926 ! s /an   pour Heino 
  • trunk/SOURCES/initial-phy-2.f90

    r4 r9  
    184184  SEALEVEL=0.0 
    185185 
    186  
    187   !     temp limit between liquid and solid precip 
    188   PSOLID=2. 
    189  
    190  
    191186  SECYEAR=365.*24.*3600. 
    192187  secyear= 31556926 ! s /an   pour Heino 
  • trunk/SOURCES/main3D-0.4-40km.f90

    r4 r9  
    240240  ! call firstoutput()           ! ouverture fichier temporel et premieres ecritures 
    241241 
    242   call forclim()                 !  initialisation BM et TS          
     242  call forclim                   !  initialisation BM et TS          
    243243  call ablation 
    244244 
  • trunk/SOURCES/steps_time_loop.f90

    r4 r9  
    260260     ! climatic forcing 
    261261     !===================== 
    262      call forclim()                               
     262     call forclim                               
    263263     call ablation 
    264264 
  • trunk/SOURCES/steps_time_loop_avec_iterbeta.f90

    r4 r9  
    266266     ! climatic forcing 
    267267     !===================== 
    268      call forclim()                               
     268     call forclim                               
    269269     call ablation 
    270270 
Note: See TracChangeset for help on using the changeset viewer.