Changeset 93 for trunk/SOURCES


Ignore:
Timestamp:
11/28/16 16:03:50 (8 years ago)
Author:
dumas
Message:

First version with Schoof flux parameterisation at the grounding line. | New module furst_schoof_mod.f90 | New flag Schoof in grdline namelist (see in SOURCES/Fichiers-parametres/A-LBq15_param_list_Schoof.dat)

Location:
trunk/SOURCES
Files:
2 added
14 edited

Legend:

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

    r66 r93  
    3535  integer ::  NZZ                       !< Total number of vertical grid points 
    3636  integer ::  err                       !< pour l'allocation des tableaux 
    37   integer ::  Igrdline                  !< si 1 fixe la position en jouant sur la fusion shelf 
     37  integer ::  igrdline                  !< si 1 fixe la position en jouant sur la fusion shelf 
    3838  integer ::  i_resolmeca               !< defini le type d'association SIA-L1 
    3939  integer ::  iter_beta                 !< pour la determination du frottement 
     
    4545  integer ::  ISYNCHRO                  !< synchronisation pas de temps dt et dtt  
    4646  integer ::  LOIGLISS                  !< permet de choisir la loi de glissement 
     47  integer ::  Schoof                    !< 0 : pas de flux de Schoof , 1 : flux de Schoof a la grounding line 
    4748  !integer ::  NYEAR                    !< number of months in 1 year, st. dev. for temp *) 
    4849  integer ::  NTMAX                     !<  
     
    298299  integer,dimension(nx,ny) :: i_Hp         !< 1 if H is prescribed on this node, else 0 
    299300  integer,dimension(nx,ny) :: i_Hp0        !< i_hp mask reference value does not change with time 
     301  integer, dimension(nx,ny) :: imx_diag    !< masque pour eq elliptique   
     302  integer, dimension(nx,ny) :: imy_diag    !< masque pour eq elliptique  
    300303  integer,dimension(nx,ny) :: MK_gl0       !< mask grounding line initial 
    301304  integer,dimension(nx,ny) :: MK_flot0     !< mask float initial 
  • trunk/SOURCES/ANT15-LBq_files/module_choix_antar15_LBq.f90

    r68 r93  
    121121                         ! enlever le use dragging dans ce cas là 
    122122 
    123  
     123use furst_schoof_mod  ! module pour calcul flux gr line 
    124124 
    125125! module concernant l'eq. elliptique (pour les streams et shelves) 
  • trunk/SOURCES/Ant40_files/module_choix-antar40-0.4.f90

    r68 r93  
    9898                          ! enlever le use dragging dans ce cas là 
    9999 
     100use furst_schoof_mod  ! module pour calcul flux gr line 
     101 
    100102! use eq_elliptique_mod ! ancienne version (remplimat-5) 
    101103use eq_ellip_sgbsv_mod ! nouvelle version juillet 2008 
  • trunk/SOURCES/Draggings_modules/dragging_prescr_beta_nolin_mod.f90

    r70 r93  
    169169    betamy_file = trim(dirnameinp)//trim(betamy_file) 
    170170    betamax = beta_limgz 
    171     betamax2d(:,:) = betamax 
    172  
     171    betamax_2d(:,:)=betamax 
    173172 
    174173!  read the beta value on centered and staggered grids 
  • trunk/SOURCES/GrIce2sea_files/module_choix_GrIce2sea.f90

    r25 r93  
    117117                          ! enlever le use dragging dans ce cas là 
    118118 
    119  
     119use furst_schoof_mod  ! module pour calcul flux gr line 
    120120 
    121121! module concernant l'eq. elliptique (pour les streams et shelves) 
    122  
    123122! use eq_elliptique_mod ! ancienne version (remplimat-5) 
    124123use eq_ellip_sgbsv_mod ! nouvelle version juillet 2008 
  • trunk/SOURCES/Hemin15_files/module_choix-hemin15.f90

    r29 r93  
    9797                          ! enlever le use dragging dans ce cas là 
    9898 
     99use furst_schoof_mod  ! module pour calcul flux gr line 
     100 
    99101! use eq_elliptique_mod ! ancienne version (remplimat-5) 
    100102use eq_ellip_sgbsv_mod ! nouvelle version juillet 2008 
  • trunk/SOURCES/Hemin40_files/module_choix-hemin40-0.4.f90

    r86 r93  
    100100                          ! enlever le use dragging dans ce cas là 
    101101 
     102use furst_schoof_mod  ! module pour calcul flux gr line 
     103 
    102104! use eq_elliptique_mod ! ancienne version (remplimat-5) 
    103105use eq_ellip_sgbsv_mod ! nouvelle version juillet 2008 
  • trunk/SOURCES/Makefile.grisli.inc

    r92 r93  
    7676        calving_frange.o no_calving.o no_lakes.o \ 
    7777        out_profile_mod.o printtable_mod.o mix-SIA-L1_mod.o \ 
     78        furst_schoof_mod.o \ 
    7879        relaxation_water_diffusion.o \ 
    7980        prescribe-H-i2s_mod.o  \ 
     
    9495        calving_frange.o no_calving.o no_lakes.o \ 
    9596        out_profile_mod.o printtable_mod.o mix-SIA-L1_mod.o \ 
     97        furst_schoof_mod.o \ 
    9698        relaxation_water_diffusion.o \ 
    9799        prescribe-H-i2s_mod.o   \ 
     
    175177 
    176178 
    177 #Liste_ANT15-LBq = lect-Ant_clim_Acc-T_gen_dat.o output_anta_mod-0.4.o \ 
    178 #       dragging-vit_bil_LBq_gen_mod.o dragging_LGM_mod.o dragging_plastic_LGM_mod.o \ 
    179 #       dragging_prescr_beta_mod.o dragging_prescr_beta_buoyency_mod.o dragging_prescr_beta_nolin_mod.o \ 
     179#Liste_ANT15-LBq = output_anta_mod-0.4.o \ 
     180#       dragging_prescr_beta_mod.o dragging_prescr_beta_nolin_mod.o \ 
    180181#       fake-routines-ant_mod.o beta_iter_vitbil_mod.o \ 
    181182#       lect-Ant_gen2010_dat.o module_choix_antar15_LBq.o \ 
    182183#       massb-ant_perturb_Tparam.o track_ant40_mod.o  
    183184 
     185 
     186# lect-Ant_clim_Acc-T_gen_dat.o dragging-vit_bil_LBq_gen_mod.o dragging_LGM_mod.o 
     187# dragging_plastic_LGM_mod.o dragging_prescr_beta_buoyency_mod.o\ 
     188 
     189 
    184190Liste_ANT15-LBq = output_anta_mod-0.4.o \ 
     191                dragging_prescr_beta_mod.o \ 
     192                dragging_prescr_beta_nolin_mod.o \ 
    185193                lect-Ant_gen2010_dat.o \ 
    186194                lect-anteis_mod.o \ 
    187195                bmelt-ant-regions_mod.o \ 
    188196                fake-routines-ant_mod.o \ 
     197                beta_iter_vitbil_mod.o \ 
    189198                module_choix_antar15_LBq.o \ 
     199                massb-ant_perturb_Tparam.o \ 
    190200                track_ant40_mod.o \ 
    191201 
     
    200210 
    201211Liste_hemin40 = output_hemin40_mod.o \ 
    202         lect-hemin40_mod.o lect-clim-act-hemin40_mod.o \ 
     212        lect-hemin40_mod.o \ 
    203213        bmelt-hemin40-regions_mod.o bmelt-hemin40-depth_mod.o \ 
    204214        fake-routines-hemin40_mod.o \ 
     
    451461Recul_ice2sea : $(Dim_ANT15-LBq) $(mod_dim_communs)  \ 
    452462        $(toy_recul) \ 
    453         $(mod_communs_RGL) \ 
    454         $(mod_clim_perturb)  \ 
    455         $(mod_tracers) \ 
     463        $(mod_communs) \ 
     464        $(mod_clim_tof)  \ 
     465        $(mod_no_tracers) \ 
    456466        $(mod_ell) $(Liste_ANT15-LBq) \ 
    457467        $(diagnoshelf) \ 
    458468        $(Liste_Netcdf) \ 
    459         $(routines_communes)steps_time_loop.o  $(routine_elliptiques)  
    460  
    461         $(LK) -o ../bin/recul_gl  $(Dim_ANT15-LBq) $(mod_dim_communs) \ 
     469        $(routines_communes) steps_time_loop.o \ 
     470        $(routine_elliptiques) \ 
     471        $(Liste_BLAS) 
     472 
     473        $(LK) -o ../bin/recul_gl \ 
     474        $(Dim_ANT15-LBq) $(mod_dim_communs) \ 
    462475        $(toy_recul) \ 
    463         $(mod_communs_RGL) \ 
    464         $(mod_clim_perturb)  \ 
    465         $(mod_tracers) \ 
    466         $(mod_ell) \ 
    467         $(Liste_ANT15-LBq) \ 
    468         $(diagnoshelf) $(Liste_Netcdf) \ 
    469         $(routines_communes) steps_time_loop.o $(routine_elliptiques) $(NCDF_LIB) $(MKL_LIB) 
     476        $(mod_communs) \ 
     477        $(mod_clim_tof)  \ 
     478        $(mod_no_tracers) \ 
     479        $(mod_ell) $(Liste_ANT15-LBq) \ 
     480        $(diagnoshelf) \ 
     481        $(Liste_Netcdf) \ 
     482        $(routines_communes) steps_time_loop.o \ 
     483        $(routine_elliptiques) $(NCDF_LIB) $(MKL_LIB) $(Liste_BLAS) 
    470484 
    471485 
  • trunk/SOURCES/New-remplimat/diagno-L2_mod.f90

    r72 r93  
    1313real, dimension(nx,ny) :: uyb1 
    1414 
    15 integer, dimension(nx,ny) :: imx_diag 
    16 integer, dimension(nx,ny) :: imy_diag 
     15!cdc transfere dans module3d pour compatibilite avec furst_schoof_mod 
     16!cdc  integer, dimension(nx,ny) :: imx_diag 
     17!cdc  integer, dimension(nx,ny) :: imy_diag 
    1718 
    1819integer :: nxd1,nxd2     ! domaine selon x Dans l'appel rempli_L2 
     
    125126 
    126127  call imx_imy_nx_ny         ! pour rempli_L2 : calcule les masques imx et imy qui  
     128 
     129!cdc debug Schoof !!!!!!!!!!!!   
     130!~   do j=1,ny 
     131!~              do i=1,nx 
     132!~                      write(578,*) uxbar(i,j) 
     133!~                      write(579,*) uybar(i,j) 
     134!~              enddo 
     135!~      enddo    
     136   
     137  if (Schoof.eq.1) then ! flux grounding line Schoof 
     138                call interpol_glflux ! calcul flux GL + interpolation sur voisins 
     139        endif    
     140         
     141!~       do j=1,ny 
     142!~              do i=1,nx 
     143!~                      write(588,*) uxbar(i,j) 
     144!~                      write(589,*) uybar(i,j) 
     145!~              enddo 
     146!~      enddo    
     147!~      print*,'ecriteure termineee !!!!!!' 
     148!~      read(*,*) 
     149         
    127150  ! donnent les cas de conditions aux limites 
    128151  ! 
  • trunk/SOURCES/Snowball_files/module_choix-snowball.f90

    r57 r93  
    9999                          ! enlever le use dragging dans ce cas là 
    100100 
     101use furst_schoof_mod  ! module pour calcul flux gr line 
     102 
    101103! use eq_elliptique_mod ! ancienne version (remplimat-5) 
    102104use eq_ellip_sgbsv_mod ! nouvelle version juillet 2008 
  • trunk/SOURCES/climat-perturb_mod-0.4.f90

    r65 r93  
    1414 
    1515use module3d_phy,only:nx,ny,S,S0,Tann,Tjuly,precip,acc,Ylat,num_forc,num_param,num_rep_42,dirforcage,dirnameinp,tafor,time,sealevel,coefbmshelf 
     16use netcdf 
     17use io_netcdf_grisli 
    1618 
    1719implicit none 
     
    4143!! Routine qui permet d'initialiser les variations temporelles des variables climatiques 
    4244!> 
    43   subroutine input_clim !routine qui permet d'initialiser les variations temporelles des variables climatiques 
     45 
     46  subroutine input_clim 
    4447 
    4548    implicit none 
     49                character(len=100) :: precip_file        ! fichier precipitations 
     50    character(len=100) :: temp_annual_file   ! fichier temperature annuelle 
     51    real               :: coef_dens          ! pour corriger si donnees en eq. eau 
     52    logical            :: temp_param         ! si utilisation de temperature parametree 
     53    real*8, dimension(:,:), pointer :: data_2D => null() ! donnees lues dans le netcdf 
     54     
     55     
    4656    character(len=8) :: control      !label to check clim. forc. file (filin) is usable 
    4757    character(len=80):: filin 
    4858    integer ::  err                       !< pour l'allocation des tableaux 
    49     integer :: i 
     59    integer :: i,j 
     60     
     61    namelist/climat_acc_T_gen/precip_file,coef_dens,temp_annual_file 
     62 
     63428 format(A) 
     64    rewind(num_param)                     ! pour revenir au debut du fichier param_list.dat 
     65    read(num_param,climat_acc_T_gen) 
     66 
     67    write(num_rep_42,428)'!___________________________________________________________'  
     68    write(num_rep_42,428)'!  module  lect_clim_acc_T_ant_gen                          ' 
     69    write(num_rep_42,climat_acc_T_gen) 
     70    write(num_rep_42,428)'!___________________________________________________________'  
     71 
     72 
     73    ! precipitation 
     74    precip_file  = trim(dirnameinp)//trim(precip_file) 
     75     
     76    call Read_ncdf_var('precip',trim(precip_file),data_2D) 
     77    precip(:,:)=data_2D(:,:) 
     78    !call lect_datfile(nx,ny,precip,1,precip_file)                   
     79 
     80    precip(:,:)=precip(:,:)*coef_dens 
     81    acc(:,:)=precip(:,:) 
     82 
     83    if ((trim(temp_annual_file).eq.'no').or.(trim(temp_annual_file).eq.'NO')) then  
     84       temp_param=.true. 
     85    else 
     86       temp_param=.false. 
     87    end if 
     88 
     89    !    temperature en surface  
     90 
     91    test_param: if (.not.temp_param) then 
     92       temp_annual_file = trim(dirnameinp)//trim(temp_annual_file) 
     93 
     94 
     95                         call Read_ncdf_var('Tann',trim(temp_annual_file),data_2D) 
     96                         Tann(:,:)=data_2D(:,:) 
     97!       call lect_input(3,'Tann',1,Tann,temp_annual_file,trim(dirnameinp)//trim(runname)//'.nc') 
     98       !call lect_datfile(nx,ny,Tann,1,temp_annual_file)               ! temperature annuelle 
     99 
     100    else                        !    parametrisation de Fortuin pour la temperature annuelle. 
     101 
     102       do j=1,ny 
     103          do i=1,nx 
     104 
     1057            if (s0(i,j).le.200.) then                                    ! shelfs 
     106                tann(i,j)=49.642-0.943*abs(ylat(i,j)) 
     107             else if ((s0(i,j).gt.200.).and.(s0(i,j).lt.1500.)) then      ! pente 
     108                tann(i,j)=36.689-0.005102*s0(i,j)-0.725*abs(ylat(i,j)) 
     109             else if (s0(i,j).ge.1500.) then                              ! plateau 
     110                tann(i,j)=7.405-0.014285*s0(i,j)-0.180*abs(ylat(i,j)) 
     111             endif 
     112          end do 
     113       end do 
     114    end if test_param 
     115 
     116    ta0(:,:)=tann(:,:) 
     117 
     118 
     119    !           pour la temperature d'ete, idem parametrisation huybrechts 
     120    do j=1,ny 
     121       do i=1,nx 
     122 
     123          tjuly(i,j)=tann(i,j)-17.65+0.00222*s0(i,j)& 
     124               +0.40802*abs(ylat(i,j)) 
     125       end do 
     126    end do 
     127 
     128 
     129 
     130 
    50131 
    51132    ! Lecture du forcage 
     
    138219 
    139220 
    140 !!!!!!!! ATTENTION AJOUTE POUR TEST MAIS A REMETTRE AU PROPRE PLUS TARD C. DUMAS !!!!!!!!!! 
    141 !!!!!!!! ancien input_climat_ref de lect_clim_act_anteis 
    142 !     accumulation de Philippe 
    143       filin='accumHUY40km.dat' 
    144       call lect_eis(nx,ny,precip,filin,DIRNAMEINP) 
    145 !====================================== La reponse est 42 =========== 
    146       write(num_rep_42,*) 'fichier accum : ', filin  
    147  
    148 !     cas particulier de Vostok 
    149       ivo=101 
    150       jvo=62 
    151       do j=jvo-1,jvo+1 
    152         do i=ivo-1,ivo+1 
    153             precip(i,j)=0.02         ! valeur plus faible a Vostok. 
    154         end do 
    155       end do 
    156       acc(:,:)=precip(:,:) 
    157  
    158 !    temperature en surface : 
    159 !    parametrisation de Fortuin pour la temperature annuelle. 
    160       do j=1,ny 
    161         do i=1,nx 
    162  
    163             if (s0(i,j).le.200.) then   ! shelfs 
    164                tann(i,j)=49.642-0.943*abs(ylat(i,j)) 
    165             else if ((s0(i,j).gt.200.).and.(s0(i,j).lt.1500.)) then ! pente 
    166                tann(i,j)=36.689-0.005102*s0(i,j)-0.725*abs(ylat(i,j)) 
    167             else if (s0(i,j).ge.1500.) then        ! plateau 
    168                tann(i,j)=7.405-0.014285*s0(i,j)-0.180*abs(ylat(i,j)) 
    169             endif 
    170  
    171             ta0(i,j)=tann(i,j) 
    172 !           pour la temperature d'ete, idem parametrisation huybrechts 
    173             tjuly(i,j)=tann(i,j)-17.65+0.00222*s0(i,j)& 
    174                          +0.40802*abs(ylat(i,j)) 
    175         end do 
    176       end do 
    177 !!!!!!!! FIN MODIF  TEMPORAIRE !!!!!!!!!! 
    178  
     221!cdc Commente pour être compatible avec lecture fichiers Cat Schoofing 
     222 
     223!~ !!!!!!!! ATTENTION AJOUTE POUR TEST MAIS A REMETTRE AU PROPRE PLUS TARD C. DUMAS !!!!!!!!!! 
     224!~ !!!!!!!! ancien input_climat_ref de lect_clim_act_anteis 
     225!~ !     accumulation de Philippe 
     226!~       filin='accumHUY40km.dat' 
     227!~       call lect_eis(nx,ny,precip,filin,DIRNAMEINP) 
     228!~ !====================================== La reponse est 42 =========== 
     229!~       write(num_rep_42,*) 'fichier accum : ', filin  
     230 
     231!~ !     cas particulier de Vostok 
     232!~       ivo=101 
     233!~       jvo=62 
     234!~       do j=jvo-1,jvo+1 
     235!~         do i=ivo-1,ivo+1 
     236!~             precip(i,j)=0.02         ! valeur plus faible a Vostok. 
     237!~         end do 
     238!~       end do 
     239!~       acc(:,:)=precip(:,:) 
     240 
     241!~ !    temperature en surface : 
     242!~ !    parametrisation de Fortuin pour la temperature annuelle. 
     243!~       do j=1,ny 
     244!~         do i=1,nx 
     245 
     246!~             if (s0(i,j).le.200.) then   ! shelfs 
     247!~                tann(i,j)=49.642-0.943*abs(ylat(i,j)) 
     248!~             else if ((s0(i,j).gt.200.).and.(s0(i,j).lt.1500.)) then ! pente 
     249!~                tann(i,j)=36.689-0.005102*s0(i,j)-0.725*abs(ylat(i,j)) 
     250!~             else if (s0(i,j).ge.1500.) then        ! plateau 
     251!~                tann(i,j)=7.405-0.014285*s0(i,j)-0.180*abs(ylat(i,j)) 
     252!~             endif 
     253 
     254!~             ta0(i,j)=tann(i,j) 
     255!~ !           pour la temperature d'ete, idem parametrisation huybrechts 
     256!~             tjuly(i,j)=tann(i,j)-17.65+0.00222*s0(i,j)& 
     257!~                          +0.40802*abs(ylat(i,j)) 
     258!~         end do 
     259!~       end do 
     260!~ !!!!!!!! FIN MODIF  TEMPORAIRE !!!!!!!!!! 
     261!cdc fin Commente pour être compatible avec lecture fichiers Cat Schoofing 
    179262 
    180263return 
  • trunk/SOURCES/deformation_mod_2lois.f90

    r73 r93  
    115115write(num_rep_42,*)'! loi de deformation 1          module deformation_mod_2lois' 
    116116write(num_rep_42,*) 
    117 write(num_rep_42,loidef_1) 
     117write(num_rep_42,*) 
    118118write(num_rep_42,*)'! exposant (glen), temperature de transition (ttrans)' 
    119119write(num_rep_42,*)'! enhancement factor (sf)' 
     
    142142write(num_rep_42,*)'! loi de deformation 2          module deformation_mod_2lois' 
    143143write(num_rep_42,*) 
    144 write(num_rep_42,loidef_2) 
     144write(num_rep_42,*) 
    145145write(num_rep_42,*)'! exposant (glen), temperature de transition (ttrans)' 
    146146write(num_rep_42,*)'! enhancement factor (sf)' 
  • trunk/SOURCES/initial-0.3.f90

    r68 r93  
    117117  call initial_heino   ! a mettre avant les init sliding et deformation 
    118118 
     119  call init_furst_schoof ! initialisation furst schoof gr line 
    119120 
    120121  call init_diagno     ! initialisation de la resolution equation elliptique vitesses  
  • trunk/SOURCES/initial-phy-2.f90

    r22 r93  
    1111!! 
    1212!< 
    13 subroutine initial_phy() 
     13subroutine initial_phy 
    1414 
    1515  !     ************************************************** 
     
    2727 
    2828  namelist/runpar/runname,icompteur,iout,reprcptr,itracebug,num_tracebug,comment_run 
    29   namelist/grdline/igrdline 
     29  namelist/grdline/igrdline,Schoof 
    3030  namelist/timesteps/dtmin,dtmax,dtt,testdiag,tbegin,tend 
    3131 
     
    122122  write(num_rep_42,*) 
    123123  write(num_rep_42,*) 'igrdline     = ',igrdline 
     124  write(num_rep_42,*) 'Schoof       = ',Schoof 
    124125  write(num_rep_42,*)'/'                            
    125   write(num_rep_42,428)'! igrdline :  1 ligne d echouage fixée, sinon 0'  
     126  write(num_rep_42,428)'! igrdline :  1 ligne d echouage fixée, sinon 0' 
     127  write(num_rep_42,428)'! Schoof   :  0 pas de Schoof, 1 flux de Schoof' 
    126128  write(num_rep_42,*) 
    127129 
Note: See TracChangeset for help on using the changeset viewer.