File: test.f90

package info (click to toggle)
eccodes 2.43.0-1
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid
  • size: 420,752 kB
  • sloc: cpp: 153,709; sh: 20,505; ansic: 12,673; f90: 6,854; python: 3,011; perl: 2,744; javascript: 1,427; yacc: 854; fortran: 468; lex: 359; makefile: 141
file content (165 lines) | stat: -rw-r--r-- 3,364 bytes parent folder | download | duplicates (3)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
integer function kind_of_long_long
  integer(2), dimension(2) :: x2 = (/1, 2/)
  integer(4), dimension(2) :: x4 = (/1, 2/)
  integer(8), dimension(2) :: x8 = (/1, 2/)
  character(len=1) :: ret

  kind_of_long_long = -1

  call check_long_long(x2(0), x2(1), ret)
  if (ret == 't') then
    kind_of_long_long = 2
    return
  end if

  call check_long_long(x4(0), x4(1), ret)
  if (ret == 't') then
    kind_of_long_long = 4
    return
  end if

  call check_long_long(x8(0), x8(1), ret)
  if (ret == 't') then
    kind_of_long_long = 8
    return
  end if

end function kind_of_long_long

integer function kind_of_size_t
  integer(2), dimension(2) :: x2 = (/1, 2/)
  integer(4), dimension(2) :: x4 = (/1, 2/)
  integer(8), dimension(2) :: x8 = (/1, 2/)
  character(len=1) :: ret

  kind_of_size_t = -1

  call check_size_t(x2(0), x2(1), ret)
  if (ret == 't') then
    kind_of_size_t = 2
    return
  end if

  call check_size_t(x4(0), x4(1), ret)
  if (ret == 't') then
    kind_of_size_t = 4
    return
  end if

  call check_size_t(x8(0), x8(1), ret)
  if (ret == 't') then
    kind_of_size_t = 8
    return
  end if

end function kind_of_size_t

integer function kind_of_long
  integer(2), dimension(2) :: x2 = (/1, 2/)
  integer(4), dimension(2) :: x4 = (/1, 2/)
  integer(8), dimension(2) :: x8 = (/1, 2/)
  character(len=1) :: ret

  kind_of_long = -1

  call check_long(x2(0), x2(1), ret)
  if (ret == 't') then
    kind_of_long = 2
    return
  end if

  call check_long(x4(0), x4(1), ret)
  if (ret == 't') then
    kind_of_long = 4
    return
  end if

  call check_long(x8(0), x8(1), ret)
  if (ret == 't') then
    kind_of_long = 8
    return
  end if

end function kind_of_long

integer function kind_of_int
  integer(2), dimension(2) :: x2 = (/1, 2/)
  integer(4), dimension(2) :: x4 = (/1, 2/)
  integer(8), dimension(2) :: x8 = (/1, 2/)
  character(len=1) :: ret

  kind_of_int = -1

  call check_int(x2(0), x2(1), ret)
  if (ret == 't') then
    kind_of_int = 2
    return
  end if

  call check_int(x4(0), x4(1), ret)
  if (ret == 't') then
    kind_of_int = 4
    return
  end if

  call check_int(x8(0), x8(1), ret)
  if (ret == 't') then
    kind_of_int = 8
    return
  end if

end function kind_of_int

integer function kind_of_float
  real(4), dimension(2) :: x4 = (/1., 2./)
  real(8), dimension(2) :: x8 = (/1., 2./)
  character(len=1) :: ret

  kind_of_float = -1

  call check_float(x4(0), x4(1), ret)
  if (ret == 't') then
    kind_of_float = 4
    return
  end if

  call check_float(x8(0), x8(1), ret)
  if (ret == 't') then
    kind_of_float = 8
    return
  end if

end function kind_of_float

integer function kind_of_double
  real(4), dimension(2) :: real4 = (/1., 2./)
  real(8), dimension(2) :: real8 = (/1., 2./)
  character(len=1) :: ret

  kind_of_double = -1

  call check_double(real4(0), real4(1), ret)
  if (ret == 't') then
    kind_of_double = 4
    return
  end if

  call check_double(real8(0), real8(1), ret)
  if (ret == 't') then
    kind_of_double = 8
    return
  end if

end function kind_of_double

program test

  print *, 'kind_of_double=', kind_of_double()
  print *, 'kind_of_float=', kind_of_float()
  print *, 'kind_of_int=', kind_of_int()
  print *, 'kind_of_long=', kind_of_long()
  print *, 'kind_of_size_t=', kind_of_size_t()
  print *, 'kind_of_long_long=', kind_of_long_long()

end program test