!> \file initial-0.3.f90 !!Initialisation du modele !< !> SUBROUTINE initial !! Cette routine permet d'initialiser le modele. !! \author ... !! \date 19 Novembre 1999 !! @note Elle appelle toutes les routines d'initialisation des differents packages. !! @note C'est cette routine qui est appellee dans le main !! @note Used modules: !! @note - use module3D_phy !! @note - use module_choix !! @note - use icetempmod !! @note - use diagno_mod !! @note - use resolmeca_SIA_L1 !! @note - use sorties_ncdf_grisli !! @note - use util_recovery !< subroutine initial use module3D_phy use module_choix use icetempmod use diagno_mod use resolmeca_SIA_L1 use flottab_mod use sorties_ncdf_grisli use util_recovery character(len=80) :: filinit !------------------------------------------------------------------------------------- ! nouvelles entrees modulaires janvier 2006 call initial_phy() ! La physique call initial2 ! Initialisation des tableaux ! call input_topo() ! La geographie !------------------------------------------------------ ! initialisation du climat (reference et forcage) !cdc call input_climat_ref() ! Le climat de reference call init_forclim ! parametres du forcage call input_clim ! lecture fichiers de forcage call init_ablation ! parametres du calcul de l'ablation !------------------------------------------------------------------------------------- ! aurel neem -> pour initialisation traceurs call init_tracer !initialisation des lacs proglaciaires call input_lakes ! call input_profile() ! Les fichiers profils ! if (icompteur.ne.0) then ! reprise d un fichier cptr call read_recovery(icompteur) !dcdmr --- GRISLI - LOVECLIM ! time = tbegin !dcdmr --- GRISLI - LOVECLIM call sortie_ncdf_cat ! else if (icompteur.eq.2) then ! reprise d'un fichier cptr mais sans la topo ! call read_recovery_temp ! else if (icompteur.eq.3) then ! reprise d'un fichier cptr mais sans la topo ni l'eau ! call read_recovery_temp ! hwater(:,:)=0. else call read_no_recovery endif !cdc call sortie_ncdf_cat ! calcul de Hmx et Hmy -> shift=-1, dim=1 -> H(i-1,j) H(:,:) = max(H(:,:),0.) hmx(:,:) = 0.5*(H(:,:)+eoshift(H(:,:),shift=-1,boundary=0.,dim=1)) hmy(:,:) = 0.5*(H(:,:)+eoshift(H(:,:),shift=-1,boundary=0.,dim=2)) hmx(:,:) = max(hmx(:,:),0.) hmy(:,:) = max(hmy(:,:),0.) call init_eaubasale ! initialise le calcul des temperatures if (geoplace(1:5).ne.'mism3') then call init_icetemp(Num_rep_42) ! initialise le calcul de temperature call thermal_prop_icetemp ! appel aux proprietes thermiques call init_bmelt ! Appel aux tableaux d'initialisation des ice shelves else ! initialisation dans le cas mismip T(:,:,:) = 0. TPMP(:,:,:) = 0. bmelt(:,:) = 0. end if !------------------------------------------------------------------------------------- !------------------------------------------------------------------------------------- call init_outshort ! initialisation sorties temporelles call init_out_hz ! initialisation des sorties call init_out_ncdf ! initialisation des sorties netcdf call init_recovery ! initialisation des sorties cptr ou nc !------------------------------------------------------------------------------------- !Appels a l'origine (2005) dans initial ! call init_iso ! initialisation de l'isostasie cette routine est dans le module ! isostasie_mod et dans noisostasie_mod call init_deformation ! initialisation de la deformation. cette routine est ! dans le module deformation_mod call init_resol_meca ! type d'association SIA L1 call initial_heino ! a mettre avant les init sliding et deformation call init_diagno ! initialisation de la resolution equation elliptique vitesses call init_sliding ! initialisation du glissement call init_spinup ! initialisation du spinup call init_dragging ! initialisation du frottement call init_icethick ! interverti avec init_dragging ! call init_dragging ! initialisation du frottement call initial_matrice ! cette routine est dans le module eq_elliptique_mod call init_calving ! !------------------------------------------------------------------------------------- ! ecriture netcdf apres initialisation !!$ if (iter_beta.eq.0) then !!$ !!$ if (itracebug.eq.1) call tracebug(' Avant appel routine icethick3') !!$ call icethick3 !!$ debug_3D(:,:,88) = S(:,:) !!$ if (itracebug.eq.1) call tracebug(' Apres appel routine icethick3') !!$ end if return end subroutine initial