Changeset 4196 for palm/trunk/SOURCE/netcdf_interface_mod.f90
- Timestamp:
- Aug 29, 2019 11:02:06 AM (5 years ago)
- File:
-
- 1 edited
Legend:
- Unmodified
- Added
- Removed
-
palm/trunk/SOURCE/netcdf_interface_mod.f90
r4182 r4196 25 25 ! ----------------- 26 26 ! $Id$ 27 ! replaced rotation angle from input-netCDF file 28 ! by namelist parameter 'rotation_angle' 29 ! 30 ! 4182 2019-08-22 15:20:23Z scharf 27 31 ! Corrected "Former revisions" section 28 32 ! … … 114 118 ONLY: biometeorology, fl_max, & 115 119 max_masks, multi_agent_system_end, & 116 multi_agent_system_start, var_fl_max, varnamelength 120 multi_agent_system_start, & 121 rotation_angle, & 122 var_fl_max, varnamelength 117 123 USE kinds 118 124 #if defined( __netcdf ) … … 544 550 LOGICAL, SAVE :: init_netcdf = .FALSE. !< 545 551 546 REAL(wp) :: cos_r a!< cosine of rotation_angle552 REAL(wp) :: cos_rot_angle !< cosine of rotation_angle 547 553 REAL(wp) :: eutm !< easting (UTM) 548 554 REAL(wp) :: nutm !< northing (UTM) 549 555 REAL(wp) :: shift_x !< shift of x coordinate 550 556 REAL(wp) :: shift_y !< shift of y coordinate 551 REAL(wp) :: sin_r a!< sine of rotation_angle557 REAL(wp) :: sin_rot_angle !< sine of rotation_angle 552 558 553 559 REAL(wp), DIMENSION(1) :: last_time_coordinate !< last time value in file … … 1026 1032 ! 1027 1033 !-- Write UTM coordinates 1028 IF ( init_model%rotation_angle == 0.0_wp ) THEN1034 IF ( rotation_angle == 0.0_wp ) THEN 1029 1035 ! 1030 1036 !-- 1D in case of no rotation 1031 cos_r a = COS( init_model%rotation_angle * pi / 180.0_wp )1037 cos_rot_angle = COS( rotation_angle * pi / 180.0_wp ) 1032 1038 ! 1033 1039 !-- x coordinates … … 1048 1054 ENDIF 1049 1055 1050 netcdf_data = init_model%origin_x + cos_r a&1056 netcdf_data = init_model%origin_x + cos_rot_angle & 1051 1057 * ( mask_i_global(mid,:mask_size(mid,1)) + shift_x ) * dx 1052 1058 … … 1077 1083 ENDIF 1078 1084 1079 netcdf_data = init_model%origin_y + cos_r a&1085 netcdf_data = init_model%origin_y + cos_rot_angle & 1080 1086 * ( mask_j_global(mid,:mask_size(mid,2)) + shift_y ) * dy 1081 1087 … … 1093 1099 !-- 2D in case of rotation 1094 1100 ALLOCATE( netcdf_data_2d(mask_size(mid,1),mask_size(mid,2)) ) 1095 cos_r a = COS( init_model%rotation_angle * pi / 180.0_wp )1096 sin_r a = SIN( init_model%rotation_angle * pi / 180.0_wp )1101 cos_rot_angle = COS( rotation_angle * pi / 180.0_wp ) 1102 sin_rot_angle = SIN( rotation_angle * pi / 180.0_wp ) 1097 1103 1098 1104 DO k = 0, 2 … … 1113 1119 DO j = 1, mask_size(mid,2) 1114 1120 DO i = 1, mask_size(mid,1) 1115 netcdf_data_2d(i,j) = init_model%origin_x &1116 + cos_r a* ( mask_i_global(mid,i) + shift_x ) * dx &1117 + sin_r a* ( mask_j_global(mid,j) + shift_y ) * dy1121 netcdf_data_2d(i,j) = init_model%origin_x & 1122 + cos_rot_angle * ( mask_i_global(mid,i) + shift_x ) * dx & 1123 + sin_rot_angle * ( mask_j_global(mid,j) + shift_y ) * dy 1118 1124 ENDDO 1119 1125 ENDDO … … 1128 1134 DO j = 1, mask_size(mid,2) 1129 1135 DO i = 1, mask_size(mid,1) 1130 netcdf_data_2d(i,j) = init_model%origin_y &1131 - sin_r a* ( mask_i_global(mid,i) + shift_x ) * dx &1132 + cos_r a* ( mask_j_global(mid,j) + shift_y ) * dy1136 netcdf_data_2d(i,j) = init_model%origin_y & 1137 - sin_rot_angle * ( mask_i_global(mid,i) + shift_x ) * dx & 1138 + cos_rot_angle * ( mask_j_global(mid,j) + shift_y ) * dy 1133 1139 ENDDO 1134 1140 ENDDO … … 1148 1154 ALLOCATE( lat(mask_size(mid,1),mask_size(mid,2)) ) 1149 1155 ALLOCATE( lon(mask_size(mid,1),mask_size(mid,2)) ) 1150 cos_r a = COS( init_model%rotation_angle * pi / 180.0_wp )1151 sin_r a = SIN( init_model%rotation_angle * pi / 180.0_wp )1156 cos_rot_angle = COS( rotation_angle * pi / 180.0_wp ) 1157 sin_rot_angle = SIN( rotation_angle * pi / 180.0_wp ) 1152 1158 1153 1159 DO k = 0, 2 … … 1168 1174 DO j = 1, mask_size(mid,2) 1169 1175 DO i = 1, mask_size(mid,1) 1170 eutm = init_model%origin_x &1171 + cos_r a* ( mask_i_global(mid,i) + shift_x ) * dx &1172 + sin_r a* ( mask_j_global(mid,j) + shift_y ) * dy1173 nutm = init_model%origin_y &1174 - sin_r a* ( mask_i_global(mid,i) + shift_x ) * dx &1175 + cos_r a* ( mask_j_global(mid,j) + shift_y ) * dy1176 eutm = init_model%origin_x & 1177 + cos_rot_angle * ( mask_i_global(mid,i) + shift_x ) * dx & 1178 + sin_rot_angle * ( mask_j_global(mid,j) + shift_y ) * dy 1179 nutm = init_model%origin_y & 1180 - sin_rot_angle * ( mask_i_global(mid,i) + shift_x ) * dx & 1181 + cos_rot_angle * ( mask_j_global(mid,j) + shift_y ) * dy 1176 1182 1177 1183 CALL convert_utm_to_geographic( crs_list, & … … 1845 1851 ! 1846 1852 !-- Write UTM coordinates 1847 IF ( init_model%rotation_angle == 0.0_wp ) THEN1853 IF ( rotation_angle == 0.0_wp ) THEN 1848 1854 ! 1849 1855 !-- 1D in case of no rotation 1850 cos_r a = COS( init_model%rotation_angle * pi / 180.0_wp )1856 cos_rot_angle = COS( rotation_angle * pi / 180.0_wp ) 1851 1857 ! 1852 1858 !-- x coordinates … … 1868 1874 1869 1875 DO i = 0, nx 1870 netcdf_data(i) = init_model%origin_x &1871 + cos_r a* ( i + shift_x ) * dx1876 netcdf_data(i) = init_model%origin_x & 1877 + cos_rot_angle * ( i + shift_x ) * dx 1872 1878 ENDDO 1873 1879 1874 1880 nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_eutm_3d(k,av),& 1875 netcdf_data, start = (/ 1 /), &1881 netcdf_data, start = (/ 1 /), & 1876 1882 count = (/ nx+1 /) ) 1877 1883 CALL netcdf_handle_error( 'netcdf_define_header', 555 ) … … 1898 1904 1899 1905 DO j = 0, ny 1900 netcdf_data(j) = init_model%origin_y &1901 + cos_r a* ( j + shift_y ) * dy1906 netcdf_data(j) = init_model%origin_y & 1907 + cos_rot_angle * ( j + shift_y ) * dy 1902 1908 ENDDO 1903 1909 1904 1910 nc_stat = NF90_PUT_VAR( id_set_3d(av), id_var_nutm_3d(k,av),& 1905 netcdf_data, start = (/ 1 /), &1911 netcdf_data, start = (/ 1 /), & 1906 1912 count = (/ ny+1 /) ) 1907 1913 CALL netcdf_handle_error( 'netcdf_define_header', 556 ) … … 1914 1920 !-- 2D in case of rotation 1915 1921 ALLOCATE( netcdf_data_2d(0:nx,0:ny) ) 1916 cos_r a = COS( init_model%rotation_angle * pi / 180.0_wp )1917 sin_r a = SIN( init_model%rotation_angle * pi / 180.0_wp )1922 cos_rot_angle = COS( rotation_angle * pi / 180.0_wp ) 1923 sin_rot_angle = SIN( rotation_angle * pi / 180.0_wp ) 1918 1924 1919 1925 DO k = 0, 2 … … 1934 1940 DO j = 0, ny 1935 1941 DO i = 0, nx 1936 netcdf_data_2d(i,j) = init_model%origin_x &1937 + cos_r a* ( i + shift_x ) * dx &1938 + sin_r a* ( j + shift_y ) * dy1942 netcdf_data_2d(i,j) = init_model%origin_x & 1943 + cos_rot_angle * ( i + shift_x ) * dx & 1944 + sin_rot_angle * ( j + shift_y ) * dy 1939 1945 ENDDO 1940 1946 ENDDO … … 1947 1953 DO j = 0, ny 1948 1954 DO i = 0, nx 1949 netcdf_data_2d(i,j) = init_model%origin_y &1950 - sin_r a* ( i + shift_x ) * dx &1951 + cos_r a* ( j + shift_y ) * dy1955 netcdf_data_2d(i,j) = init_model%origin_y & 1956 - sin_rot_angle * ( i + shift_x ) * dx & 1957 + cos_rot_angle * ( j + shift_y ) * dy 1952 1958 ENDDO 1953 1959 ENDDO … … 1999 2005 ALLOCATE( lat(nxl:nxr,nys:nyn) ) 2000 2006 ALLOCATE( lon(nxl:nxr,nys:nyn) ) 2001 cos_r a = COS( init_model%rotation_angle * pi / 180.0_wp )2002 sin_r a = SIN( init_model%rotation_angle * pi / 180.0_wp )2007 cos_rot_angle = COS( rotation_angle * pi / 180.0_wp ) 2008 sin_rot_angle = SIN( rotation_angle * pi / 180.0_wp ) 2003 2009 2004 2010 DO k = 0, 2 … … 2019 2025 DO j = nys, nyn 2020 2026 DO i = nxl, nxr 2021 eutm = init_model%origin_x &2022 + cos_r a* ( i + shift_x ) * dx &2023 + sin_r a* ( j + shift_y ) * dy2024 nutm = init_model%origin_y &2025 - sin_r a* ( i + shift_x ) * dx &2026 + cos_r a* ( j + shift_y ) * dy2027 eutm = init_model%origin_x & 2028 + cos_rot_angle * ( i + shift_x ) * dx & 2029 + sin_rot_angle * ( j + shift_y ) * dy 2030 nutm = init_model%origin_y & 2031 - sin_rot_angle * ( i + shift_x ) * dx & 2032 + cos_rot_angle * ( j + shift_y ) * dy 2027 2033 2028 2034 CALL convert_utm_to_geographic( crs_list, & … … 2913 2919 ! 2914 2920 !-- Write UTM coordinates 2915 IF ( init_model%rotation_angle == 0.0_wp ) THEN2921 IF ( rotation_angle == 0.0_wp ) THEN 2916 2922 ! 2917 2923 !-- 1D in case of no rotation 2918 cos_r a = COS( init_model%rotation_angle * pi / 180.0_wp )2924 cos_rot_angle = COS( rotation_angle * pi / 180.0_wp ) 2919 2925 ! 2920 2926 !-- x coordinates … … 2936 2942 2937 2943 DO i = 0, nx 2938 netcdf_data(i) = init_model%origin_x &2939 + cos_r a* ( i + shift_x ) * dx2944 netcdf_data(i) = init_model%origin_x & 2945 + cos_rot_angle * ( i + shift_x ) * dx 2940 2946 ENDDO 2941 2947 2942 2948 nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_eutm_xy(k,av),& 2943 netcdf_data, start = (/ 1 /), &2949 netcdf_data, start = (/ 1 /), & 2944 2950 count = (/ nx+1 /) ) 2945 2951 CALL netcdf_handle_error( 'netcdf_define_header', 555 ) … … 2966 2972 2967 2973 DO j = 0, ny 2968 netcdf_data(j) = init_model%origin_y &2969 + cos_r a* ( j + shift_y ) * dy2974 netcdf_data(j) = init_model%origin_y & 2975 + cos_rot_angle * ( j + shift_y ) * dy 2970 2976 ENDDO 2971 2977 2972 2978 nc_stat = NF90_PUT_VAR( id_set_xy(av), id_var_nutm_xy(k,av),& 2973 netcdf_data, start = (/ 1 /), &2979 netcdf_data, start = (/ 1 /), & 2974 2980 count = (/ ny+1 /) ) 2975 2981 CALL netcdf_handle_error( 'netcdf_define_header', 556 ) … … 2982 2988 !-- 2D in case of rotation 2983 2989 ALLOCATE( netcdf_data_2d(0:nx,0:ny) ) 2984 cos_r a = COS( init_model%rotation_angle * pi / 180.0_wp )2985 sin_r a = SIN( init_model%rotation_angle * pi / 180.0_wp )2990 cos_rot_angle = COS( rotation_angle * pi / 180.0_wp ) 2991 sin_rot_angle = SIN( rotation_angle * pi / 180.0_wp ) 2986 2992 2987 2993 DO k = 0, 2 … … 3002 3008 DO j = 0, ny 3003 3009 DO i = 0, nx 3004 netcdf_data_2d(i,j) = init_model%origin_x &3005 + cos_r a* ( i + shift_x ) * dx &3006 + sin_r a* ( j + shift_y ) * dy3010 netcdf_data_2d(i,j) = init_model%origin_x & 3011 + cos_rot_angle * ( i + shift_x ) * dx & 3012 + sin_rot_angle * ( j + shift_y ) * dy 3007 3013 ENDDO 3008 3014 ENDDO … … 3015 3021 DO j = 0, ny 3016 3022 DO i = 0, nx 3017 netcdf_data_2d(i,j) = init_model%origin_y &3018 - sin_r a* ( i + shift_x ) * dx &3019 + cos_r a* ( j + shift_y ) * dy3023 netcdf_data_2d(i,j) = init_model%origin_y & 3024 - sin_rot_angle * ( i + shift_x ) * dx & 3025 + cos_rot_angle * ( j + shift_y ) * dy 3020 3026 ENDDO 3021 3027 ENDDO … … 3037 3043 ALLOCATE( lat(nxl:nxr,nys:nyn) ) 3038 3044 ALLOCATE( lon(nxl:nxr,nys:nyn) ) 3039 cos_r a = COS( init_model%rotation_angle * pi / 180.0_wp )3040 sin_r a = SIN( init_model%rotation_angle * pi / 180.0_wp )3045 cos_rot_angle = COS( rotation_angle * pi / 180.0_wp ) 3046 sin_rot_angle = SIN( rotation_angle * pi / 180.0_wp ) 3041 3047 3042 3048 DO k = 0, 2 … … 3057 3063 DO j = nys, nyn 3058 3064 DO i = nxl, nxr 3059 eutm = init_model%origin_x &3060 + cos_r a* ( i + shift_x ) * dx &3061 + sin_r a* ( j + shift_y ) * dy3062 nutm = init_model%origin_y &3063 - sin_r a* ( i + shift_x ) * dx &3064 + cos_r a* ( j + shift_y ) * dy3065 eutm = init_model%origin_x & 3066 + cos_rot_angle * ( i + shift_x ) * dx & 3067 + sin_rot_angle * ( j + shift_y ) * dy 3068 nutm = init_model%origin_y & 3069 - sin_rot_angle * ( i + shift_x ) * dx & 3070 + cos_rot_angle * ( j + shift_y ) * dy 3065 3071 3066 3072 CALL convert_utm_to_geographic( crs_list, & … … 3798 3804 ! 3799 3805 !-- Write UTM coordinates 3800 IF ( init_model%rotation_angle == 0.0_wp ) THEN3806 IF ( rotation_angle == 0.0_wp ) THEN 3801 3807 ! 3802 3808 !-- 1D in case of no rotation 3803 cos_r a = COS( init_model%rotation_angle * pi / 180.0_wp )3809 cos_rot_angle = COS( rotation_angle * pi / 180.0_wp ) 3804 3810 ! 3805 3811 !-- x coordinates … … 3821 3827 3822 3828 DO i = 0, nx 3823 netcdf_data(i) = init_model%origin_x &3824 + cos_r a* ( i + shift_x ) * dx3829 netcdf_data(i) = init_model%origin_x & 3830 + cos_rot_angle * ( i + shift_x ) * dx 3825 3831 ENDDO 3826 3832 3827 3833 nc_stat = NF90_PUT_VAR( id_set_xz(av), id_var_eutm_xz(k,av),& 3828 netcdf_data, start = (/ 1 /), &3834 netcdf_data, start = (/ 1 /), & 3829 3835 count = (/ nx+1 /) ) 3830 3836 CALL netcdf_handle_error( 'netcdf_define_header', 555 ) … … 3855 3861 ELSE 3856 3862 netcdf_data(i) = init_model%origin_y & 3857 + cos_r a* ( section(i,2) + shift_y ) * dy3863 + cos_rot_angle * ( section(i,2) + shift_y ) * dy 3858 3864 ENDIF 3859 3865 ENDDO … … 3871 3877 !-- 2D in case of rotation 3872 3878 ALLOCATE( netcdf_data_2d(0:nx,1:ns) ) 3873 cos_r a = COS( init_model%rotation_angle * pi / 180.0_wp )3874 sin_r a = SIN( init_model%rotation_angle * pi / 180.0_wp )3879 cos_rot_angle = COS( rotation_angle * pi / 180.0_wp ) 3880 sin_rot_angle = SIN( rotation_angle * pi / 180.0_wp ) 3875 3881 3876 3882 DO k = 0, 2 … … 3894 3900 ELSE 3895 3901 DO i = 0, nx 3896 netcdf_data_2d(i,j) = init_model%origin_x &3897 + cos_r a* ( i + shift_x ) * dx &3898 + sin_r a* ( section(j,2) + shift_y ) * dy3902 netcdf_data_2d(i,j) = init_model%origin_x & 3903 + cos_rot_angle * ( i + shift_x ) * dx & 3904 + sin_rot_angle * ( section(j,2) + shift_y ) * dy 3899 3905 ENDDO 3900 3906 ENDIF … … 3911 3917 ELSE 3912 3918 DO i = 0, nx 3913 netcdf_data_2d(i,j) = init_model%origin_y &3914 - sin_r a* ( i + shift_x ) * dx &3915 + cos_r a* ( section(j,2) + shift_y ) * dy3919 netcdf_data_2d(i,j) = init_model%origin_y & 3920 - sin_rot_angle * ( i + shift_x ) * dx & 3921 + cos_rot_angle * ( section(j,2) + shift_y ) * dy 3916 3922 ENDDO 3917 3923 ENDIF … … 3930 3936 ALLOCATE( lat(0:nx,1:ns) ) 3931 3937 ALLOCATE( lon(0:nx,1:ns) ) 3932 cos_r a = COS( init_model%rotation_angle * pi / 180.0_wp )3933 sin_r a = SIN( init_model%rotation_angle * pi / 180.0_wp )3938 cos_rot_angle = COS( rotation_angle * pi / 180.0_wp ) 3939 sin_rot_angle = SIN( rotation_angle * pi / 180.0_wp ) 3934 3940 3935 3941 DO k = 0, 2 … … 3954 3960 ELSE 3955 3961 DO i = 0, nx 3956 eutm = init_model%origin_x &3957 + cos_r a* ( i + shift_x ) * dx &3958 + sin_r a* ( section(j,2) + shift_y ) * dy3959 nutm = init_model%origin_y &3960 - sin_r a* ( i + shift_x ) * dx &3961 + cos_r a* ( section(j,2) + shift_y ) * dy3962 eutm = init_model%origin_x & 3963 + cos_rot_angle * ( i + shift_x ) * dx & 3964 + sin_rot_angle * ( section(j,2) + shift_y ) * dy 3965 nutm = init_model%origin_y & 3966 - sin_rot_angle * ( i + shift_x ) * dx & 3967 + cos_rot_angle * ( section(j,2) + shift_y ) * dy 3962 3968 3963 3969 CALL convert_utm_to_geographic( crs_list, & … … 4648 4654 ! 4649 4655 !-- Write UTM coordinates 4650 IF ( init_model%rotation_angle == 0.0_wp ) THEN4656 IF ( rotation_angle == 0.0_wp ) THEN 4651 4657 ! 4652 4658 !-- 1D in case of no rotation 4653 cos_r a = COS( init_model%rotation_angle * pi / 180.0_wp )4659 cos_rot_angle = COS( rotation_angle * pi / 180.0_wp ) 4654 4660 ! 4655 4661 !-- x coordinates … … 4675 4681 ELSE 4676 4682 netcdf_data(i) = init_model%origin_x & 4677 + cos_r a* ( section(i,3) + shift_x ) * dx4683 + cos_rot_angle * ( section(i,3) + shift_x ) * dx 4678 4684 ENDIF 4679 4685 ENDDO … … 4705 4711 4706 4712 DO i = 0, ny 4707 netcdf_data(i) = init_model%origin_y &4708 + cos_r a* ( i + shift_y ) * dy4713 netcdf_data(i) = init_model%origin_y & 4714 + cos_rot_angle * ( i + shift_y ) * dy 4709 4715 ENDDO 4710 4716 … … 4721 4727 !-- 2D in case of rotation 4722 4728 ALLOCATE( netcdf_data_2d(1:ns,0:ny) ) 4723 cos_r a = COS( init_model%rotation_angle * pi / 180.0_wp )4724 sin_r a = SIN( init_model%rotation_angle * pi / 180.0_wp )4729 cos_rot_angle = COS( rotation_angle * pi / 180.0_wp ) 4730 sin_rot_angle = SIN( rotation_angle * pi / 180.0_wp ) 4725 4731 4726 4732 DO k = 0, 2 … … 4744 4750 netcdf_data_2d(i,:) = -1.0_wp !section averaged along x 4745 4751 ELSE 4746 netcdf_data_2d(i,j) = init_model%origin_x &4747 + cos_r a* ( section(i,3) + shift_x ) * dx &4748 + sin_r a* ( j + shift_y ) * dy4752 netcdf_data_2d(i,j) = init_model%origin_x & 4753 + cos_rot_angle * ( section(i,3) + shift_x ) * dx & 4754 + sin_rot_angle * ( j + shift_y ) * dy 4749 4755 ENDIF 4750 4756 ENDDO … … 4761 4767 netcdf_data_2d(i,:) = -1.0_wp !section averaged along x 4762 4768 ELSE 4763 netcdf_data_2d(i,j) = init_model%origin_y &4764 - sin_r a* ( section(i,3) + shift_x ) * dx &4765 + cos_r a* ( j + shift_y ) * dy4769 netcdf_data_2d(i,j) = init_model%origin_y & 4770 - sin_rot_angle * ( section(i,3) + shift_x ) * dx & 4771 + cos_rot_angle * ( j + shift_y ) * dy 4766 4772 ENDIF 4767 4773 ENDDO … … 4780 4786 ALLOCATE( lat(1:ns,0:ny) ) 4781 4787 ALLOCATE( lon(1:ns,0:ny) ) 4782 cos_r a = COS( init_model%rotation_angle * pi / 180.0_wp )4783 sin_r a = SIN( init_model%rotation_angle * pi / 180.0_wp )4788 cos_rot_angle = COS( rotation_angle * pi / 180.0_wp ) 4789 sin_rot_angle = SIN( rotation_angle * pi / 180.0_wp ) 4784 4790 4785 4791 DO k = 0, 2 … … 4804 4810 lon(i,:) = -180.0_wp ! section averaged along x 4805 4811 ELSE 4806 eutm = init_model%origin_x &4807 + cos_r a* ( section(i,3) + shift_x ) * dx &4808 + sin_r a* ( j + shift_y ) * dy4809 nutm = init_model%origin_y &4810 - sin_r a* ( section(i,3) + shift_x ) * dx &4811 + cos_r a* ( j + shift_y ) * dy4812 eutm = init_model%origin_x & 4813 + cos_rot_angle * ( section(i,3) + shift_x ) * dx & 4814 + sin_rot_angle * ( j + shift_y ) * dy 4815 nutm = init_model%origin_y & 4816 - sin_rot_angle * ( section(i,3) + shift_x ) * dx & 4817 + cos_rot_angle * ( j + shift_y ) * dy 4812 4818 4813 4819 CALL convert_utm_to_geographic( crs_list, & … … 6906 6912 nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'origin_z', init_model%origin_z ) 6907 6913 CALL netcdf_handle_error( 'netcdf_create_global_atts 11', error_no ) 6908 nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'rotation_angle', init_model%rotation_angle )6914 nc_stat = NF90_PUT_ATT( ncid, NF90_GLOBAL, 'rotation_angle', rotation_angle ) 6909 6915 CALL netcdf_handle_error( 'netcdf_create_global_atts 12', error_no ) 6910 6916 … … 7047 7053 ! 7048 7054 !-- Define UTM coordinates 7049 IF ( init_model%rotation_angle == 0.0_wp ) THEN7055 IF ( rotation_angle == 0.0_wp ) THEN 7050 7056 CALL netcdf_create_var( id_set, (/ id_dim_x(0) /), 'E_UTM', NF90_DOUBLE, id_var_eutm(0), 'm', 'easting', 000, 000, 000 ) 7051 7057 CALL netcdf_create_var( id_set, (/ id_dim_y(0) /), 'N_UTM', NF90_DOUBLE, id_var_nutm(0), 'm', 'northing', 000, 000, 000 )
Note: See TracChangeset
for help on using the changeset viewer.