mod_raw_io.F 11 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394
  1. module mod_raw_io
  2. contains
  3. ! Modified from Alan Wallcraft's RAW routine by Knut Liseter @ NERSC
  4. ! So far only the "I" in "IO" is present
  5. SUBROUTINE READRAW(A,AMN,AMX,IDM,JDM,LSPVAL,SPVAL,CFILE1,K)
  6. IMPLICIT NONE
  7. C
  8. REAL*4 SPVALH
  9. PARAMETER (SPVALH=1.0E30_4)
  10. C
  11. REAL*4, INTENT(OUT) :: A(IDM,JDM)
  12. REAL*4, INTENT(OUT) :: AMN,AMX
  13. INTEGER, INTENT(IN) :: IDM,JDM
  14. LOGICAL, INTENT(IN) :: LSPVAL
  15. REAL*4, INTENT(INOUT) :: SPVAL
  16. INTEGER, INTENT(IN) :: K
  17. CHARACTER(len=*), INTENT(IN) :: CFILE1
  18. C
  19. REAL*4 :: PADA(4096)
  20. C
  21. C MOST OF WORK IS DONE HERE.
  22. C
  23. INTEGER LEN_TRIM
  24. INTEGER I,J,IOS,NRECL
  25. INTEGER NPAD
  26. C
  27. IF(.NOT.LSPVAL) THEN
  28. SPVAL = SPVALH
  29. ENDIF
  30. C
  31. !!! Calculate the number of elements padded!!!!!!!!!!!!!!!!!!!!!!!!
  32. NPAD=GET_NPAD(IDM,JDM)
  33. C
  34. INQUIRE( IOLENGTH=NRECL) A,PADA(1:NPAD)
  35. C
  36. C
  37. OPEN(UNIT=11, FILE=CFILE1, FORM='UNFORMATTED', STATUS='old',
  38. + ACCESS='DIRECT', RECL=NRECL, IOSTAT=IOS, ACTION='READ')
  39. IF (IOS.NE.0) THEN
  40. write(6,*) 'Error: can''t open ',CFILE1(1:LEN_TRIM(CFILE1))
  41. write(6,*) 'ios = ',ios
  42. write(6,*) 'nrecl = ',nrecl
  43. CALL EXIT(3)
  44. ENDIF
  45. C
  46. READ(11,REC=K,IOSTAT=IOS) A
  47. close(11)
  48. C
  49. IF (IOS.NE.0) THEN
  50. WRITE(6,*) 'can''t read record ',K,
  51. & ' from '//CFILE1(1:LEN_TRIM(CFILE1))
  52. CALL EXIT(4)
  53. ENDIF
  54. C
  55. AMN = SPVALH
  56. AMX = -SPVALH
  57. DO J= 1,JDM
  58. DO I=1,IDM
  59. IF (A(I,J).LE.SPVALH) THEN
  60. AMN = MIN(real(AMN, 4), real(A(I,J), 4))
  61. AMX = MAX(real(AMX, 4), real(A(I,J), 4))
  62. ELSEIF (LSPVAL) THEN
  63. A(I,J) = SPVAL
  64. ENDIF
  65. END DO
  66. END DO
  67. C
  68. RETURN
  69. END SUBROUTINE
  70. ! Modified from Alan Wallcraft's RAW routine by Knut Liseter @ NERSC
  71. ! This wll be the "O" in "IO" is present
  72. SUBROUTINE WRITERAW(A,AMN,AMX,IDM,JDM,LSPVAL,SPVAL,CFILE1,K)
  73. IMPLICIT NONE
  74. C
  75. REAL*4 SPVALH
  76. PARAMETER (SPVALH=1.0e30_4)
  77. C
  78. REAL*4, INTENT(INOUT) :: A(IDM,JDM)
  79. REAL*4, INTENT(OUT) :: AMN,AMX
  80. INTEGER, INTENT(IN) :: IDM,JDM
  81. LOGICAL, INTENT(IN) :: LSPVAL
  82. REAL*4, INTENT(INOUT) :: SPVAL
  83. INTEGER, INTENT(IN) :: K
  84. CHARACTER(len=*), INTENT(IN) :: CFILE1
  85. C
  86. REAL*4 :: PADA(4096)
  87. C
  88. C MOST OF WORK IS DONE HERE.
  89. C
  90. INTEGER LEN_TRIM
  91. INTEGER I,J,IOS,NRECL
  92. INTEGER NPAD
  93. C
  94. IF(.NOT.LSPVAL) THEN
  95. SPVAL = SPVALH
  96. ENDIF
  97. C
  98. !!! Calculate the number of elements padded!!!!!!!!!!!!!!!!!!!!!!!!
  99. NPAD=GET_NPAD(IDM,JDM)
  100. C
  101. PADA=0.
  102. INQUIRE( IOLENGTH=NRECL) A,PADA(1:NPAD)
  103. C
  104. C
  105. OPEN(UNIT=11, FILE=CFILE1, FORM='UNFORMATTED', STATUS='unknown',
  106. + ACCESS='DIRECT', RECL=NRECL, IOSTAT=IOS)
  107. IF (IOS.NE.0) THEN
  108. write(6,*) 'Error: can''t open ',CFILE1(1:LEN_TRIM(CFILE1))
  109. write(6,*) 'ios = ',ios
  110. write(6,*) 'nrecl = ',nrecl
  111. CALL EXIT(3)
  112. ENDIF
  113. C
  114. WRITE(11,REC=K,IOSTAT=IOS) A,PADA(1:NPAD)
  115. close(11)
  116. C
  117. IF (IOS.NE.0) THEN
  118. WRITE(6,*) 'can''t write record ',K,
  119. & ' from '//CFILE1(1:LEN_TRIM(CFILE1))
  120. CALL EXIT(4)
  121. ENDIF
  122. C
  123. AMN = SPVALH
  124. AMX = -SPVALH
  125. DO J= 1,JDM
  126. DO I=1,IDM
  127. IF (A(I,J).LE.SPVALH) THEN
  128. AMN = MIN(real(AMN, 4), real(A(I,J), 4))
  129. AMX = MAX(real(AMX, 4), real(A(I,J), 4))
  130. ELSEIF (LSPVAL) THEN
  131. A(I,J) = SPVAL
  132. ENDIF
  133. END DO
  134. END DO
  135. C
  136. RETURN
  137. END SUBROUTINE
  138. !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
  139. ! Routine to get index of fields in data file (.a) from header file (.b)
  140. subroutine rst_index_from_header(fname,cfld,vlevel,tlevel,
  141. & indx,bmin,bmax,skiphdr)
  142. implicit none
  143. character(len=*), intent(in) :: fname ! filename without extention
  144. character(len=*), intent(in) :: cfld ! variable name
  145. integer , intent(in) :: tlevel ! time level
  146. integer , intent(in) :: vlevel ! vertical level
  147. integer , intent(out):: indx ! index in .a file
  148. real , intent(out):: bmin,bmax ! min and max from b file
  149. logical , intent(in) :: skiphdr
  150. integer :: itlevel, ivlevel
  151. character(len=8) :: icfld
  152. integer :: ios,i
  153. integer :: nskip_rst,nop
  154. logical :: match, ex
  155. nskip_rst=2
  156. nop = 999
  157. ! Open file
  158. inquire(exist=ex,file=trim(fname))
  159. if (.not. ex) then
  160. print *,'file '//trim(fname)//' is not present'
  161. call exit(1)
  162. end if
  163. open(nop,file=trim(fname),status='old',action='read')
  164. ! Skip first nskip lines
  165. if (skiphdr) then
  166. do i=1,nskip_rst
  167. read(nop,*)
  168. end do
  169. end if
  170. match=.false.
  171. indx=0
  172. ios=0
  173. do while (ios==0 .and. .not.match)
  174. read(nop,117,iostat=ios) icfld,ivlevel,itlevel,bmin,bmax
  175. match= icfld==cfld .and. ivlevel==vlevel .and. itlevel==tlevel
  176. indx=indx+1
  177. !print *,icfld,itlevel,ivlevel,bmin,bmax
  178. end do
  179. close(nop)
  180. if (.not.match) then
  181. !print *,'Could not find field '//cfld
  182. !print *,'Vertical level :',vlevel
  183. !print *,'Time level :',tlevel
  184. indx=-1
  185. !call exit(1) ! Always return to caller
  186. endif
  187. 117 format (a8,23x,i3,i3,2x,2e16.7)
  188. end subroutine
  189. !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
  190. ! Routine to get field desc in header file (.b) from index in data file (.a)
  191. subroutine rst_header_from_index(fname,cfld,vlevel,tlevel,
  192. & indx,bmin,bmax,skiphdr)
  193. implicit none
  194. character(len=*), intent(in) :: fname ! filename without extention
  195. character(len=8), intent(out) :: cfld ! variable name
  196. integer , intent(out) :: tlevel ! time level
  197. integer , intent(out) :: vlevel ! vertical level
  198. integer , intent(in) :: indx ! index in .a file
  199. real , intent(out) :: bmin,bmax ! min and max from b file
  200. logical , intent(in ) :: skiphdr ! Skip header of .b file
  201. integer :: ios,i
  202. integer :: nskip_rst,nop
  203. logical :: ex
  204. nskip_rst=2
  205. nop = 999
  206. ! Open file
  207. inquire(exist=ex,file=trim(fname))
  208. if (.not. ex) then
  209. print *,'file '//trim(fname)//' not present'
  210. call exit(1)
  211. end if
  212. open(nop,file=trim(fname),status='old',action='read')
  213. ! Skip first nskip + index-1 lines
  214. !print *,'hei'
  215. if (skiphdr) then
  216. do i=1,nskip_rst
  217. read(nop,*)
  218. end do
  219. end if
  220. do i=1,indx-1
  221. read(nop,*)
  222. end do
  223. read(nop,117,iostat=ios) cfld,vlevel,tlevel,bmin,bmax
  224. close(nop)
  225. if (ios/=0) then
  226. !print *,'Could not get info from index',indx
  227. !call exit(1)
  228. cfld=''
  229. tlevel=-1
  230. vlevel=-1
  231. endif
  232. 117 format (a8,23x,i3,i3,2x,2e16.7)
  233. end subroutine
  234. !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
  235. ! Routine to get index of fields in regional grid file (.a) from header file (.b)
  236. subroutine grid_index_from_header(fname,cfld,indx,bmin,bmax
  237. & ,skiphdr)
  238. implicit none
  239. character(len=*), intent(in) :: fname ! filename without extention
  240. character(len=*), intent(in) :: cfld ! variable name
  241. integer , intent(out):: indx ! index in .a file
  242. real , intent(out):: bmin,bmax ! min and max from b file
  243. logical , intent(in) :: skiphdr
  244. character(len=4) :: icfld
  245. character*80 :: cline
  246. integer :: ios,i
  247. integer :: nskip_grid,nop
  248. logical :: match, ex
  249. nskip_grid=3
  250. nop = 999
  251. ! Open file
  252. inquire(exist=ex,file=trim(fname))
  253. if (.not. ex) then
  254. print *,'file '//trim(fname)//' is not present'
  255. call exit(1)
  256. end if
  257. open(nop,file=trim(fname),status='old',action='read')
  258. ! Skip first nskip lines
  259. if (skiphdr) then
  260. do i=1,nskip_grid
  261. read(nop,*)
  262. end do
  263. end if
  264. match=.false.
  265. indx=0
  266. ios=0
  267. do while (ios==0 .and. .not.match)
  268. read(nop,'(a)') cline
  269. icfld=cline(1:4)
  270. i=index(cline,'=')
  271. read (cline(i+1:),*) bmin,bmax
  272. match= trim(icfld)==trim(cfld)
  273. indx=indx+1
  274. end do
  275. close(nop)
  276. if (.not.match) then
  277. indx=-1
  278. endif
  279. end subroutine grid_index_from_header
  280. !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
  281. !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
  282. ! Routine to get index of fields in regional grid file (.a) from header file (.b)
  283. subroutine daily_index_from_header(fname,cfld,coord,indx,
  284. & bmin,bmax)
  285. implicit none
  286. character(len=*), intent(in) :: fname ! filename without extention
  287. character(len=*), intent(in) :: cfld ! variable name
  288. integer , intent(in) :: coord ! vertical coordinate
  289. integer , intent(out):: indx ! index in .a file
  290. real , intent(out):: bmin,bmax ! min and max from b file
  291. logical, parameter:: skiphdr=.true.
  292. character(len=5) :: char5
  293. character(len=8) :: char8
  294. integer :: ios
  295. integer :: nop
  296. logical :: match, ex
  297. real :: dens,rday
  298. integer :: lcoord,nstep
  299. nop = 999
  300. ! Open file
  301. inquire(exist=ex,file=trim(fname))
  302. if (.not. ex) then
  303. print *,'file '//trim(fname)//' is not present'
  304. call exit(1)
  305. end if
  306. open(nop,file=trim(fname),status='old')
  307. ! Skip first nskip lines
  308. if (skiphdr) then
  309. do while (char5/='field' .and. ios==0)
  310. read(nop,'(a5)',iostat=ios) char5
  311. end do
  312. end if
  313. ! Read until we get the field we want
  314. indx=0
  315. ios=0
  316. char8=''
  317. lcoord=-1
  318. match=.false.
  319. do while(.not.match .and. ios==0)
  320. read(nop,117,iostat=ios) char8,nstep,rday,lcoord,dens,
  321. & bmin,bmax
  322. match=(trim(cfld)==trim(char8) .and. lcoord==coord)
  323. indx=indx+1
  324. end do
  325. close(nop)
  326. if (.not.match) then
  327. indx=-1
  328. endif
  329. 117 format (a8,' = ',i11,f11.2,i3,f7.3,1p2e16.7)
  330. end subroutine daily_index_from_header
  331. !!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!!
  332. INTEGER FUNCTION GET_NPAD(IDM,JDM)
  333. IMPLICIT NONE
  334. INTEGER, INTENT(IN) :: IDM,JDM
  335. GET_NPAD = 4096 - MOD(IDM*JDM,4096)
  336. GET_NPAD = mod(GET_NPAD,4096)
  337. END FUNCTION
  338. end module mod_raw_io