c-lamp_rewrite.f90
author Forrest Hoffman <forrest@climatemodeling.org>
Sun, 21 Sep 2008 21:59:01 -0400
changeset 0 c8ca04c3a9d6
permissions -rw-r--r--
Initial commit of code to rewrite C-LAMP output from CLM3 for the Earth System Grid (ESG)
forrest@0
     1
  program clamp_rewrite
forrest@0
     2
forrest@0
     3
! Program to use CMOR routines to rewrite model results from the simulations
forrest@0
     4
! for the Carbon-Land Model Intercomparison Project (C-LAMP).
forrest@0
     5
!
forrest@0
     6
! Forrest M. Hoffman <forrest@climatemodeling.org>
forrest@0
     7
! Created: Fri Jun  8 11:50:01 EDT 2007
forrest@0
     8
forrest@0
     9
forrest@0
    10
    use cmor_users_functions
forrest@0
    11
    use netcdf
forrest@0
    12
    use kind_mod
forrest@0
    13
    use clm_mod, only: namelen, varnamelen, coord, var_data, &
forrest@0
    14
      clm_read_coord, clm_copy_grid_data, clm_read_data, clm_convert_data, &
forrest@0
    15
      clm_free_data
forrest@0
    16
    implicit none
forrest@0
    17
forrest@0
    18
    integer, parameter :: maxf = 2500
forrest@0
    19
    integer, parameter :: maxv = 200
forrest@0
    20
    integer :: i, numf, numv
forrest@0
    21
forrest@0
    22
    integer, allocatable :: iaxis(:)          ! CMOR handle for axes (time, [hour,] [z-level,] latitude, longitude)
forrest@0
    23
    integer              :: ivar              ! CMOR handle for variable
forrest@0
    24
    integer              :: ierr              ! error flag
forrest@0
    25
    integer              :: axis_num          ! axis counter
forrest@0
    26
    integer              :: realization       ! model run realization
forrest@0
    27
    character (len=128)  :: input_path        ! input path
forrest@0
    28
    character (len=128)  :: fnames(maxf) = '' ! input file names
forrest@0
    29
    integer              :: tshift(maxf) = 0  ! time shift for files
forrest@0
    30
    character (len=128)  :: output_path       ! output path
forrest@0
    31
    character (len=128)  :: input_table       ! CMOR table path
forrest@0
    32
    character (len=32)   :: vnames(maxv) = '' ! input variable names
forrest@0
    33
    character (len=256)  :: source = ''       ! source global attribute
forrest@0
    34
    character (len=128)  :: experiment = ''   ! experiment_id global attribute
forrest@0
    35
    logical              :: casa_flux_bug     ! scale fluxes due to bug in CASA'
forrest@0
    36
forrest@0
    37
    real(r4) :: imissing = 1.0e+36 ! missing-data flag on input
forrest@0
    38
    real(r4) :: omissing = 1.0e+36 ! missing-data flag on output
forrest@0
    39
forrest@0
    40
    casa_flux_bug = .false.
forrest@0
    41
forrest@0
    42
    namelist /inparm/ input_table, output_path, experiment, source, &
forrest@0
    43
      realization, input_path, fnames, tshift, vnames, casa_flux_bug
forrest@0
    44
forrest@0
    45
    open(10, file='namelist', status='old')
forrest@0
    46
    ierr = 1
forrest@0
    47
    do while(ierr /= 0)
forrest@0
    48
      read(10, inparm, iostat=ierr)
forrest@0
    49
      if (ierr < 0) then
forrest@0
    50
        stop 'End of file on namelist read'
forrest@0
    51
      end if
forrest@0
    52
    end do
forrest@0
    53
    close(10)
forrest@0
    54
forrest@0
    55
    ! Count number of input data files
forrest@0
    56
    numf = 0
forrest@0
    57
    do i = 1, maxf
forrest@0
    58
       if (trim(fnames(i)) /= '') numf = numf + 1
forrest@0
    59
    end do
forrest@0
    60
    ! Count number of variables
forrest@0
    61
    numv = 0
forrest@0
    62
    do i = 1, maxv
forrest@0
    63
       if (trim(vnames(i)) /= '') numv = numv + 1
forrest@0
    64
    end do
forrest@0
    65
forrest@0
    66
    print *, 'Reading input files for coordinates and counts...'
forrest@0
    67
    call clm_read_coord(numf, input_path, fnames, .true.)
forrest@0
    68
forrest@0
    69
    do i = 1, numv
forrest@0
    70
      select case (vnames(i))
forrest@0
    71
      ! gca
forrest@0
    72
      case ('area')
forrest@0
    73
         call clm_copy_grid_data(vnames(i))
forrest@0
    74
      ! lbm
forrest@0
    75
      case ('landmask')
forrest@0
    76
         call clm_copy_grid_data(vnames(i))
forrest@0
    77
      ! orog
forrest@0
    78
      case ('topo')
forrest@0
    79
         call clm_copy_grid_data(vnames(i))
forrest@0
    80
      ! sftlf
forrest@0
    81
      case ('landfrac')
forrest@0
    82
         call clm_copy_grid_data(vnames(i))
forrest@0
    83
      case default
forrest@0
    84
         print *, 'Reading input files for variable ', vnames(i)
forrest@0
    85
         call clm_read_data(numf, input_path, fnames, tshift, vnames(i))
forrest@0
    86
forrest@0
    87
         !print *,'var_data%varname = ',var_data%varname
forrest@0
    88
         !print *,'var_data%ndims = ',var_data%ndims
forrest@0
    89
         !print *,'var_data%time = ',var_data%time
forrest@0
    90
         !print *,'var_data%long_name = ',trim(var_data%long_name)
forrest@0
    91
         !print *,'var_data%missing_value = ',var_data%missing_value
forrest@0
    92
         !print *,'var_data%units = ',trim(var_data%units)
forrest@0
    93
      end select
forrest@0
    94
forrest@0
    95
      print *, 'Performing unit conversion on data...'
forrest@0
    96
      call clm_convert_data(casa_flux_bug)
forrest@0
    97
forrest@0
    98
      print *, 'Initializing CMOR...'
forrest@0
    99
      ierr = cmor_setup(inpath='./',netcdf_file_action='preserve', &
forrest@0
   100
        set_verbosity=2, exit_control=2)
forrest@0
   101
forrest@0
   102
      print *, 'Identifying output data sets for CMOR...'
forrest@0
   103
      ierr = cmor_dataset(                                              &
forrest@0
   104
        outpath       = output_path,                                    &
forrest@0
   105
        experiment_id = experiment,                                     &
forrest@0
   106
        institution   = 'ORNL (Oak Ridge National Laboratory, Oak Ridge, Tennessee, USA)', &
forrest@0
   107
        source        = trim(source),                                   &
forrest@0
   108
        realization   = realization,                                    &
forrest@0
   109
        calendar      = 'noleap',                                       &
forrest@0
   110
        history       = 'Extracted from case '//trim(coord%case_id),    &
forrest@0
   111
        comment       = 'Initial dataset: '//trim(coord%inidat)//       &
forrest@0
   112
          '; surface dataset: '//trim(coord%surdat)//'; pft dataset: '//&
forrest@0
   113
          trim(coord%pftdat)//'; rtm dataset: '//trim(coord%rtmdat),    &
forrest@0
   114
        references    = 'http://www.climatemodeling.org/c-lamp',        &
forrest@0
   115
        contact       = 'Forrest M. Hoffman <forrest@climatemodeling.org>')
forrest@0
   116
forrest@0
   117
      allocate(iaxis(var_data%ndims), stat=ierr)
forrest@0
   118
      if (ierr /= 0) then
forrest@0
   119
         print *, 'Cannot allocate iaxis'
forrest@0
   120
         stop
forrest@0
   121
      end if
forrest@0
   122
forrest@0
   123
      print *, 'Defining coordinates for CMOR output data...'
forrest@0
   124
      axis_num = 1
forrest@0
   125
forrest@0
   126
      iaxis(axis_num) = cmor_axis(                                      &
forrest@0
   127
        table       = input_table,                                      &
forrest@0
   128
        table_entry = 'longitude',                                      &
forrest@0
   129
        units       = 'degrees_east',                                   &
forrest@0
   130
        length      = coord%xsize,                                      &
forrest@0
   131
        coord_vals  = coord%x)
forrest@0
   132
      axis_num = axis_num + 1
forrest@0
   133
forrest@0
   134
      iaxis(axis_num) = cmor_axis(                                      &
forrest@0
   135
        table       = input_table,                                      &
forrest@0
   136
        table_entry = 'latitude',                                       &
forrest@0
   137
        units       = 'degrees_north',                                  &
forrest@0
   138
        length      = coord%ysize,                                      &
forrest@0
   139
        coord_vals  = coord%y)
forrest@0
   140
      axis_num = axis_num + 1
forrest@0
   141
forrest@0
   142
      if (var_data%soil_layer_flag) then
forrest@0
   143
         iaxis(axis_num) = cmor_axis(                                   &
forrest@0
   144
           table       = input_table,                                   &
forrest@0
   145
           table_entry = 'depth_soil',                                  &
forrest@0
   146
           units       = 'm',                                           &
forrest@0
   147
           length      = coord%zsoi_size,                               &
forrest@0
   148
           coord_vals  = coord%zsoi)
forrest@0
   149
         axis_num = axis_num + 1
forrest@0
   150
      end if
forrest@0
   151
forrest@0
   152
      if (var_data%hour_flag) then
forrest@0
   153
         iaxis(axis_num) = cmor_axis(                                   &
forrest@0
   154
           table       = input_table,                                   &
forrest@0
   155
           table_entry = 'hour',                                        &
forrest@0
   156
           units       = 'hours',                                       &
forrest@0
   157
           length      = coord%hr_size,                                 &
forrest@0
   158
           coord_vals  = coord%hr)
forrest@0
   159
         axis_num = axis_num + 1
forrest@0
   160
      end if
forrest@0
   161
forrest@0
   162
      if (var_data%ndims > 2) then
forrest@0
   163
        iaxis(axis_num) = cmor_axis(                                    &
forrest@0
   164
          table       = input_table,                                    &
forrest@0
   165
          table_entry = 'time',                                         &
forrest@0
   166
          units       = 'days since 1798-01-01 00:00:00')
forrest@0
   167
        axis_num = axis_num + 1
forrest@0
   168
      end if
forrest@0
   169
forrest@0
   170
      print *, 'Defining CMOR output data variables...'
forrest@0
   171
      if (var_data%positive == '') then
forrest@0
   172
         ivar = cmor_variable(                                          &
forrest@0
   173
           table         = input_table,                                 &
forrest@0
   174
           table_entry   = var_data%out_varname,                        &
forrest@0
   175
           original_name = var_data%varname,                            &
forrest@0
   176
           units         = var_data%units,                              &
forrest@0
   177
           missing_value = var_data%missing_value,                      &
forrest@0
   178
           axis_ids      = iaxis)
forrest@0
   179
      else
forrest@0
   180
         ivar = cmor_variable(                                          &
forrest@0
   181
           table         = input_table,                                 &
forrest@0
   182
           table_entry   = var_data%out_varname,                        &
forrest@0
   183
           original_name = var_data%varname,                            &
forrest@0
   184
           units         = var_data%units,                              &
forrest@0
   185
           positive      = var_data%positive,                           &
forrest@0
   186
           missing_value = var_data%missing_value,                      &
forrest@0
   187
           axis_ids      = iaxis)
forrest@0
   188
      end if
forrest@0
   189
forrest@0
   190
      print *, 'Writing CMOR output...'
forrest@0
   191
      select case (var_data%ndims)
forrest@0
   192
         case (2)
forrest@0
   193
            if (var_data%int_type) then
forrest@0
   194
               ierr = cmor_write(                                       &
forrest@0
   195
                 var_id    = ivar,                                      &
forrest@0
   196
                 data      = var_data%int2d)
forrest@0
   197
            else
forrest@0
   198
               ierr = cmor_write(                                       &
forrest@0
   199
                 var_id    = ivar,                                      &
forrest@0
   200
                 data      = var_data%var2d)
forrest@0
   201
            end if
forrest@0
   202
         case (3)
forrest@0
   203
            ierr = cmor_write(                                          &
forrest@0
   204
              var_id    = ivar,                                         &
forrest@0
   205
              data      = var_data%var3d,                               &
forrest@0
   206
              time_vals = var_data%time,                                &
forrest@0
   207
              time_bnds = var_data%time_bounds)
forrest@0
   208
         case (4)
forrest@0
   209
            ierr = cmor_write(                                          &
forrest@0
   210
              var_id    = ivar,                                         &
forrest@0
   211
              data      = var_data%var4d,                               &
forrest@0
   212
              time_vals = var_data%time,                                &
forrest@0
   213
              time_bnds = var_data%time_bounds)
forrest@0
   214
         case default
forrest@0
   215
            print *, 'Unable to handle data with ', var_data%ndims, 'dimensions'
forrest@0
   216
            stop
forrest@0
   217
      end select
forrest@0
   218
forrest@0
   219
      print *, 'Closing CMOR file(s)...'
forrest@0
   220
      ierr = cmor_close()
forrest@0
   221
forrest@0
   222
      deallocate(iaxis)
forrest@0
   223
forrest@0
   224
      print *, 'Freeing data...'
forrest@0
   225
      call clm_free_data()
forrest@0
   226
forrest@0
   227
    end do ! loop over variables
forrest@0
   228
forrest@0
   229
  end program clamp_rewrite