Changeset 272 for LMDZ.3.3/branches


Ignore:
Timestamp:
Sep 5, 2001, 6:11:26 PM (23 years ago)
Author:
lmdzadmin
Message:

Rajout de profils de variables par fichiers et non plus globaux
Redefinition des chaines de caracteres passees
LF

File:
1 edited

Legend:

Unmodified
Added
Removed
  • LMDZ.3.3/branches/rel-LF/libf/bibio/writephys.F90

    r266 r272  
    5151     integer,dimension(:), pointer :: reg_index
    5252  end type profils
    53   type (profils), dimension(nb_prof_max), save :: var_profs
     53  type (profils), dimension(nb_prof_max, nb_files_max), save :: var_profs
    5454
    5555! liste des variables par fichier
     
    8787! Declaration des parametres d'entree
    8888  integer :: nid_file
    89   character (len=30) :: nom_fichier
     89  character*(*) :: nom_fichier
    9090  integer :: iim, jjm, llm, klon
    9191  real, dimension(iim) :: rlon
     
    105105  if (first_call) then
    106106    hist_files(:)%define = .true.
    107     var_profs(:)%freq_wri = -999
     107    var_profs(:,:)%freq_wri = -999
    108108    hist_files(:)%nitau = 1
    109109    first_call= .false.
     
    152152!###########################################################################
    153153!
    154   SUBROUTINE writephy_def(profil_n, var_op, freq_op, freq_wri, zsize, &
     154  SUBROUTINE writephy_def(profil_n, nid_file,               &
     155 &                        var_op, freq_op, freq_wri, zsize, &
    155156 &                        reg_size, reg_index)
    156157!
     
    160161! Parametres d'entree
    161162!   profil_n      numero du profil-type
     163!   nid_file      numero de fichier
    162164!   var_op        operation a effectuer sur la variable
    163165!   freq_op       frequence de l'operation
     
    168170!
    169171  integer                         :: profil_n
    170   character (len = 6)             :: var_op
     172  integer                         :: nid_file
     173  character*(*)             :: var_op
    171174  real                            :: freq_op, freq_wri
    172175  integer                         :: zsize
     
    188191    call abort_gcm(modname, message, 1)
    189192  endif
    190   if (var_profs(profil_n)%freq_wri /= -999) then
     193  if (var_profs(profil_n, nid_file)%freq_wri /= -999) then
    191194    message = 'numero de profil deja attribue'
    192195    call abort_gcm(modname, message, 1)
     
    195198! Remplissage structure infos
    196199!
    197   var_profs(profil_n)%var_op = var_op
    198   var_profs(profil_n)%freq_op = freq_op
    199   var_profs(profil_n)%freq_wri = freq_wri
    200   var_profs(profil_n)%zsize = zsize
     200  var_profs(profil_n, nid_file)%var_op = var_op
     201  var_profs(profil_n, nid_file)%freq_op = freq_op
     202  var_profs(profil_n, nid_file)%freq_wri = freq_wri
     203  var_profs(profil_n, nid_file)%zsize = zsize
    201204!
    202205! test pour region
     
    207210      call abort_gcm(modname, message, 1)
    208211    endif
    209     allocate(var_profs(profil_n)%reg_index(reg_size), stat = error)
     212    allocate(var_profs(profil_n, nid_file)%reg_index(reg_size), stat = error)
    210213    if (error /= 0) then
    211214      message='Pb allocation reg_index'
    212215      call abort_gcm(modname,message,1)
    213216    endif
    214     var_profs(profil_n)%reg_size = reg_size
    215     var_profs(profil_n)%reg_index = reg_index(1:reg_size)
     217    var_profs(profil_n, nid_file)%reg_size = reg_size
     218    var_profs(profil_n, nid_file)%reg_index = reg_index(1:reg_size)
    216219  else
    217220    dummy_size = 1
    218     allocate(var_profs(profil_n)%reg_index(dummy_size), stat = error)
     221    allocate(var_profs(profil_n, nid_file)%reg_index(dummy_size), stat = error)
    219222    if (error /= 0) then
    220223      message='Pb allocation reg_index'
    221224      call abort_gcm(modname,message,1)
    222225    endif
    223     var_profs(profil_n)%reg_size = dummy_size
    224     var_profs(profil_n)%reg_index = 0
     226    var_profs(profil_n, nid_file)%reg_size = dummy_size
     227    var_profs(profil_n, nid_file)%reg_index = 0
    225228  endif
    226229
    227230  write(nulou,*)' Definition du profil de variable numero ', profil_n
    228   write(nulou,*)'     operation               ',var_profs(profil_n)%var_op
    229   write(nulou,*)'     frequence d''operation  ',var_profs(profil_n)%freq_op
    230   write(nulou,*)'     frequence d''ecriture   ',var_profs(profil_n)%freq_wri
    231   write(nulou,*)'     2D/3D                   ',var_profs(profil_n)%zsize
    232   write(nulou,*)'     taille de la region     ',var_profs(profil_n)%reg_size
     231  write(nulou,*)'                              du fichier ', nid_file
     232  write(nulou,*)'     operation               ', &
     233 &                    var_profs(profil_n, nid_file)%var_op
     234  write(nulou,*)'     frequence d''operation  ', &
     235 &                    var_profs(profil_n, nid_file)%freq_op
     236  write(nulou,*)'     frequence d''ecriture   ', &
     237 &                    var_profs(profil_n, nid_file)%freq_wri
     238  write(nulou,*)'     2D/3D                   ', &
     239 &                    var_profs(profil_n, nid_file)%zsize
     240  write(nulou,*)'     taille de la region     ', &
     241 &                    var_profs(profil_n, nid_file)%reg_size
    233242
    234243  END SUBROUTINE writephy_def
     
    253262
    254263  integer              :: file, iprof
    255   character (len=10)   :: var_name
     264  character*(*)        :: var_name
    256265  real, dimension(*)   :: data
    257   character (len=40)   :: var_title
    258   character (len=20)   :: var_units
     266  character*(*)        :: var_title
     267  character*(*)        :: var_units
    259268!
    260269! variables locales
    261270!
    262271  integer              :: i, error
    263   character (len=6)   :: var_op
     272  character (len=6)    :: var_op
    264273  real                 :: freq_op, freq_wri
    265274  integer              :: file_id, isize, jsize, lsize, phy_lon, zsize
     
    290299      nhori = hist_files(file)%nhori
    291300      klon = hist_files(file)%phy_lon
    292       var_op = var_profs(iprof)%var_op
    293       freq_op = var_profs(iprof)%freq_op
    294       freq_wri = var_profs(iprof)%freq_wri
    295       if (var_profs(iprof)%zsize == 0) then
     301      var_op = var_profs(iprof, file)%var_op
     302      freq_op = var_profs(iprof, file)%freq_op
     303      freq_wri = var_profs(iprof, file)%freq_wri
     304      if (var_profs(iprof, file)%zsize == 0) then
    296305        lsize = 1
    297306        nvert = -99
     
    316325  jsize = hist_files(file)%jsize   
    317326  nhori = hist_files(file)%nhori
    318   var_op = var_profs(iprof)%var_op
    319   freq_op = var_profs(iprof)%freq_op
    320   freq_wri = var_profs(iprof)%freq_wri
     327  var_op = var_profs(iprof, file)%var_op
     328  freq_op = var_profs(iprof, file)%freq_op
     329  freq_wri = var_profs(iprof, file)%freq_wri
    321330  nitau = hist_files(file)%nitau
    322331
    323   if (var_profs(iprof)%zsize == 0) then
     332  if (var_profs(iprof, file)%zsize == 0) then
    324333    lsize = 1
    325334  else
     
    336345  call gr_fi_ecrit(lsize, klon, isize, jsize, data, temp_data)
    337346  call histwrite(file_id, var_name,nitau,temp_data, &
    338  &               var_profs(iprof)%reg_size,var_profs(iprof)%reg_index)
     347 &               var_profs(iprof, file)%reg_size, &
     348 &               var_profs(iprof, file)%reg_index)
    339349   
    340350  return
Note: See TracChangeset for help on using the changeset viewer.