Skip to content
Snippets Groups Projects
sfx_z0t_all.f90 10.3 KiB
Newer Older
  • Learn to ignore specific revisions
  • module sfx_z0t_all
       
      !< @brief surface thermal roughness parameterizations for all type surface
    
    
        use sfx_z0t_all_surface
    
        
    
        implicit none
        public :: get_thermal_roughness_all
        public :: get_thermal_roughness_definition
    
        integer, public, parameter :: surface_ocean = 0     !< ocean surface
        integer, public, parameter :: surface_land = 1      !< land surface
        integer, public, parameter :: surface_lake = 2      !< lake surface
        integer, public, parameter :: surface_snow = 3      !< snow covered surface    
        integer, public, parameter :: surface_forest = 4    !< forest surface  
        integer, public, parameter :: surface_user = 5      !< user surface  
    
        
        integer, public, parameter :: z0t_kl_water = 0 
        integer, public, parameter :: z0t_kl_land = 1   
        integer, public, parameter :: z0t_re = 2      
        integer, public, parameter :: z0t_zi = 3         
        integer, public, parameter :: z0t_ca = 4    
        integer, public, parameter :: z0t_cz = 5      
        integer, public, parameter :: z0t_br = 6      
        integer, public, parameter :: z0t_ot = 7      
        integer, public, parameter :: z0t_du = 8      
        integer, public, parameter :: z0t_zm = 9      
        integer, public, parameter :: z0t_mix = 10      
        integer, public, parameter :: z0t_user = 11     
    
    
    
        character(len = 16), parameter :: surface_ocean_tag = 'ocean'
        character(len = 16), parameter :: surface_land_tag = 'land'
        character(len = 16), parameter :: surface_lake_tag = 'lake'
        character(len = 16), parameter :: surface_snow_tag = 'snow'
        character(len = 16), parameter :: surface_forest_tag = 'forest'
        character(len = 16), parameter :: surface_user_tag = 'user'
    
        character(len = 16), parameter :: z0t_tag_kl_water = 'kl_water'
        character(len = 16), parameter :: z0t_tag_kl_land = 'kl_land'
        character(len = 16), parameter :: z0t_tag_re = 're'
        character(len = 16), parameter :: z0t_tag_zi = 'zi'
        character(len = 16), parameter :: z0t_tag_ca = 'ca'
        character(len = 16), parameter :: z0t_tag_cz = 'cz'
        character(len = 16), parameter :: z0t_tag_br = 'br'
        character(len = 16), parameter :: z0t_tag_ot = 'ot'
        character(len = 16), parameter :: z0t_tag_du = 'du'
        character(len = 16), parameter :: z0t_tag_zm = 'zm'
        character(len = 16), parameter :: z0t_tag_mix = 'mix'
        character(len = 16), parameter :: z0t_tag_user = 'zt_user'
    
        integer, public, parameter :: ocean_z0t_id = z0t_kl_water     !< ocean surface
        integer, public, parameter :: land_z0t_id = z0t_kl_land        !< land surface
        integer, public, parameter :: lake_z0t_id = z0t_re        !< lake surface
        integer, public, parameter :: snow_z0t_id = z0t_ca        !< snow covered surface    
        integer, public, parameter :: forest_z0t_id = z0t_du      !< forest csurface  
        integer, public, parameter :: usersf_z0t_id = z0t_mix       !< user surface  
       
       
        contains
    
    
      ! surface type definition
        ! --------------------------------------------------------------------------------
        function get_surface_id(tag) result(id)
            implicit none
            character(len=*), intent(in) :: tag
            integer :: id
    
            id = - 1
            if (trim(tag) == trim(surface_ocean_tag)) then
                id = surface_ocean
            else if (trim(tag) == trim(surface_land_tag)) then
                id = surface_land
            else if (trim(tag) == trim(surface_lake_tag)) then
                id = surface_lake
            else if (trim(tag) == trim(surface_snow_tag)) then
                id = surface_snow
            end if
    
        end function
    
        function get_surface_tag(id) result(tag)
            implicit none
            integer :: id
            character(len=:), allocatable :: tag
    
            tag = 'undefined'
            if (id == surface_ocean) then
                tag = surface_ocean_tag
            else if (id == surface_land) then
                tag = surface_land_tag
            else if (id == surface_lake) then
                tag = surface_lake_tag
            else if (id == surface_snow) then
                tag = surface_snow_tag
            end if 
    
        end function
    
        
          ! --------------------------------------------------------------------------------
         ! surface type definition
        ! --------------------------------------------------------------------------------
        function get_surface_z0t_id(tag_z0t) result(z0t_id)
            implicit none
            character(len=*), intent(in) :: tag_z0t
            integer :: z0t_id
    
            z0t_id = - 1
            if (trim(tag_z0t) == trim(z0t_tag_kl_water)) then
                z0t_id = z0t_kl_water
            else if (trim(tag_z0t) == trim(z0t_tag_kl_land)) then
                z0t_id = z0t_kl_land
            else if (trim(tag_z0t) == trim(z0t_tag_re)) then
                z0t_id = z0t_re
            else if (trim(tag_z0t) == trim(z0t_tag_zi)) then
                z0t_id = z0t_zi
            else if (trim(tag_z0t) == trim(z0t_tag_ca)) then
                z0t_id = z0t_ca
            else if (trim(tag_z0t) == trim(z0t_tag_cz)) then
                z0t_id = z0t_cz
            else if (trim(tag_z0t) == trim(z0t_tag_br)) then
                z0t_id = z0t_br
            else if (trim(tag_z0t) == trim(z0t_tag_ot)) then
                z0t_id = z0t_ot
            else if (trim(tag_z0t) == trim(z0t_tag_du)) then
                z0t_id = z0t_du
            else if (trim(tag_z0t) == trim(z0t_tag_zm)) then
                z0t_id = z0t_zm
            else if (trim(tag_z0t) == trim(z0t_tag_mix)) then
                z0t_id = z0t_mix
            else if (trim(tag_z0t) == trim(z0t_tag_user)) then
                z0t_id = z0t_user
            end if
    
        end function
    
        function get_surface_z0t_tag(z0t_id) result(tag_z0t)
            implicit none
            integer :: z0t_id
            character(len=:), allocatable :: tag_z0t
    
            tag_z0t = 'undefined'
            if (z0t_id == z0t_kl_water) then
                tag_z0t = z0t_tag_kl_water
            else if (z0t_id == z0t_kl_land) then
                tag_z0t =  z0t_tag_kl_land
            else if (z0t_id == z0t_re) then
                tag_z0t = z0t_tag_re
            else if (z0t_id == z0t_zi) then
                tag_z0t = z0t_tag_zi
            else if (z0t_id == z0t_ca) then
                tag_z0t = z0t_tag_ca
            else if (z0t_id == z0t_cz) then
                tag_z0t = z0t_tag_cz
            else if (z0t_id == z0t_br) then
                tag_z0t = z0t_tag_br
            else if (z0t_id == z0t_ot) then
                tag_z0t = z0t_tag_ot
            else if (z0t_id == z0t_du) then
                tag_z0t = z0t_tag_du
            else if (z0t_id == z0t_zm) then
                tag_z0t = z0t_tag_zm
            else if (z0t_id == z0t_mix) then
                tag_z0t = z0t_tag_mix
            else if (z0t_id == z0t_user) then
                tag_z0t = z0t_tag_user
            end if 
         end function
    
    
    
         ! ----------------------------------------------------------------------------
           subroutine get_thermal_roughness_all(z0_t, B, &
                z0_m, Re, u_dyn, Czm, LAI, z0t_id)
         ! ----------------------------------------------------------------------------
            real, intent(out) :: z0_t               !< thermal roughness [m]
            real, intent(out) :: B                  !< = log(z0_m / z0_t) [n/d]
    
            real, intent(in) :: z0_m                !< aerodynamic roughness [m]
            real, intent(in) :: Re                  !< roughness Reynolds number [n/d]
            real, intent(in) :: LAI                 !< leaf-area index
            real, intent(in) :: u_dyn              !< dynamic velocity [m/s]
            real, intent(in) :: Czm                 !< proportionality coefficient z0_t =Czm*z0_m
    
           integer, intent(in) :: z0t_id
         ! ---------------------------------------------------------------------------
    
    
           if (z0t_id == z0t_kl_water) then
            call get_thermal_roughness_kl_water(z0_t, B, z0_m, Re)
        else if (z0t_id == z0t_kl_land) then
            call get_thermal_roughness_kl_land(z0_t, B, z0_m, Re)
        else if (z0t_id == z0t_re) then
            call get_thermal_roughness_re(z0_t, B, z0_m, Re)
        else if (z0t_id == z0t_zi) then
            call get_thermal_roughness_zi(z0_t, B, z0_m, Re)
        else if (z0t_id == z0t_ca) then
            call get_thermal_roughness_ca(z0_t, B, z0_m, Re)
        else if (z0t_id == z0t_cz) then
            call get_thermal_roughness_cz(z0_t, B, z0_m, Re)
        else if (z0t_id == z0t_br) then
            call get_thermal_roughness_br(z0_t, B, z0_m, Re)
        else if (z0t_id == z0t_ot) then
            call get_thermal_roughness_ot(z0_t, B, z0_m, Re)
        else if (z0t_id == z0t_du) then
            call get_thermal_roughness_du(z0_t, B, z0_m, u_dyn, LAI)
        else if (z0t_id == z0t_zm) then
            call get_thermal_roughness_zm(z0_t, B, z0_m, Czm)
        else if (z0t_id == z0t_mix) then
            call get_thermal_roughness_mix(z0_t, B, z0_m, u_dyn, Re)
        else if (z0t_id == z0t_user) then
            write(*, *) 'z0t_user'
        end if
    
    
        write (*,*) z0_t, B, z0_m, Re, u_dyn, Czm, LAI, z0t_id
    
         end subroutine
        ! --------------------------------------------------------------------------------  
       
       ! ----------------------------------------------------------------------------
           subroutine get_thermal_roughness_definition(surface_type, id_ocean, id_land, id_snow, id_lake, &
            id_forest, id_user, ocean_z0t_id, land_z0t_id, lake_z0t_id, snow_z0t_id, &
            forest_z0t_id, usersf_z0t_id)
         ! ----------------------------------------------------------------------------
            real, intent(out) :: ocean_z0t_id              
            real, intent(out) :: land_z0t_id                 
            real, intent(out) :: lake_z0t_id  
            real, intent(out) :: snow_z0t_id 
            real, intent(out) :: forest_z0t_id  
            real, intent(out) :: usersf_z0t_id 
    
            real, intent(in) :: surface_type             
    
            real, intent(in) :: id_ocean              
            real, intent(in) :: id_land               
            real, intent(in) :: id_snow 
            real, intent(in) :: id_lake
            real, intent(in) :: id_forest  
            real, intent(in) :: id_user
            
         ! ---------------------------------------------------------------------------
    
         if (surface_type == surface_ocean) then
             ocean_z0t_id = id_ocean
         else if (surface_type == surface_land) then
             land_z0t_id = id_land
         else if (surface_type == surface_snow) then
             snow_z0t_id = id_snow
         else if (surface_type == surface_lake) then
            lake_z0t_id = id_lake
         else if (surface_type == surface_forest) then
             forest_z0t_id = id_forest
         else if (surface_type == surface_user) then
             usersf_z0t_id  = id_user
         end if 
         end subroutine
    
    end module sfx_z0t_all