module convload use typedef, only: & int32, real64 implicit none character(len=*), parameter :: & convert = 'big_endian' integer(kind=int32), parameter :: & cnv_start = 1024 real(kind=real64), parameter :: & cnv_fac = 0.5d0 * (sqrt(5.d0) + 1.d0) contains subroutine loadconv(namecnv, ifirst, ilast) use convdata, only: & convtype, data implicit none character(len=*), intent(in):: & namecnv integer(kind=int32), intent(IN) :: & ifirst, ilast integer(kind=int32):: & iunit, n, i, & nvers, nmodel, & iostat type(convtype) :: & cnv type(convtype), dimension(:), allocatable :: & data1 if (allocated(data)) & deallocate(data) n = cnv_start allocate(data(n)) open(NEWUNIT=iunit, & FILE=namecnv, & STATUS='OLD', & POSITION='REWIND', & FORM='UNFORMATTED', & CONVERT=convert) ! call fseek(UNIT=iunit, OFFSET=ifirst, WHENCE=0) do while (.True.) READ(iunit,IOSTAT=iostat) nvers, nmodel if (IS_IOSTAT_END(iostat)) & exit if (iostat /= 0) & error stop '[loadconv] Error finding record' if (nmodel >= ifirst) then backspace(iunit) exit endif enddo do i = 1, 2**30 cnv = loadconv_10600(iunit) if (cnv%nvers == 0) & exit if (cnv%ncyc > ilast) & exit if (i > n) then n = int(n * cnv_fac) allocate(data1(n)) data1(1:i-1) = data(1:i-1) deallocate(data) call move_alloc(data1, data) endif data(i) = cnv enddo close(UNIT=iunit, STATUS='keep') n = i-1 allocate(data1(n)) data1(1:n) = data(1:n) deallocate(data) call move_alloc(data1, data) print*, '[loadconv] Loaded models', data(1)%ncyc, ' - ', data(n)%ncyc end subroutine loadconv function loadconv_10600(iunit) result(cnv) use typedef, only: & int32 use convdata, only: & convtype, & nuc_kind_len, idx_kind_len integer(kind=int32), parameter :: & nvers = 10600 integer(kind=int32), intent(IN):: & iunit type(convtype) :: & cnv integer(kind=int32) :: & iostat read(iunit, IOSTAT=iostat) & cnv%nvers, & cnv%ncyc,& cnv%timesec, & cnv%dt, & cnv%nconv, & cnv%nnuc, & cnv%nnuk, & cnv%nneu, & cnv%nnucd, & cnv%nnukd, & cnv%nneud, & cnv%ncoord, & cnv%idx_kind_len, & cnv%nuc_kind_len if (cnv%nvers /= nvers) error stop 'version mismatch' if (cnv%idx_kind_len /= idx_kind_len) error stop 'idx_kind_len mismatch' if (cnv%nuc_kind_len /= nuc_kind_len) error stop 'nuc_kind_len mismatch' if (IS_IOSTAT_END(iostat)) then cnv%nvers = 0 return endif allocate(& cnv%nuc(cnv%nnuc), & cnv%nuk(cnv%nnuk), & cnv%neu(cnv%nneu), & cnv%nucd(cnv%nnucd), & cnv%nukd(cnv%nnukd), & cnv%neud(cnv%nneud), & cnv%yzip(cnv%nconv), & cnv%xmcoord(cnv%ncoord), & cnv%rncoord(cnv%ncoord), & cnv%inuc(cnv%nnuc), & cnv%inuk(cnv%nnuk), & cnv%ineu(cnv%nneu), & cnv%inucd(cnv%nnucd), & cnv%inukd(cnv%nnukd), & cnv%ineud(cnv%nneud), & cnv%iconv(cnv%nconv)) backspace(iunit) read(iunit) & cnv%nvers, & cnv%ncyc,& cnv%timesec, & cnv%dt, & cnv%nconv, & cnv%nnuc, & cnv%nnuk, & cnv%nneu, & cnv%nnucd, & cnv%nnukd, & cnv%nneud, & cnv%ncoord, & cnv%idx_kind_len, & cnv%nuc_kind_len, & cnv%nuc, & cnv%nuk, & cnv%neu, & cnv%nucd, & cnv%nukd, & cnv%neud, & cnv%yzip, & cnv%xmcoord, & cnv%rncoord, & cnv%ladv cnv%nadv = popcnt(cnv%ladv) backspace(iunit) allocate(& cnv%iadv(cnv%nadv), & cnv%dmadv(cnv%nadv), & cnv%dvadv(cnv%nadv)) read(iunit) & cnv%nvers, & cnv%ncyc,& cnv%timesec, & cnv%dt, & cnv%nconv, & cnv%nnuc, & cnv%nnuk, & cnv%nneu, & cnv%nnucd, & cnv%nnukd, & cnv%nneud, & cnv%ncoord, & cnv%idx_kind_len, & cnv%nuc_kind_len, & cnv%nuc, & cnv%nuk, & cnv%neu, & cnv%nucd, & cnv%nukd, & cnv%neud, & cnv%yzip, & cnv%xmcoord, & cnv%rncoord, & cnv%ladv, & cnv%iadv, & cnv%dmadv, & cnv%dvadv, & cnv%inuc, & cnv%inuk, & cnv%ineu, & cnv%inucd, & cnv%inukd, & cnv%ineud, & cnv%iconv, & cnv%levcnv, & cnv%minloss, & cnv%mingain, & cnv%minnucl, & cnv%minnucg, & cnv%minneul, & cnv%minneug, & cnv%minlossd, & cnv%mingaind, & cnv%minnucld, & cnv%minnucgd, & cnv%minneuld, & cnv%minneugd, & cnv%tc, & cnv%dc, & cnv%pc, & cnv%ec, & cnv%sc, & cnv%ye, & cnv%ab, & cnv%et, & cnv%sn, & cnv%su, & cnv%g1, & cnv%g2, & cnv%s1, & cnv%s2, & cnv%aw, & cnv%summ0, & cnv%radius0, & cnv%an, & cnv%abun, & cnv%eni , & cnv%enk , & cnv%enp , & cnv%ent , & cnv%epro , & cnv%enn , & cnv%enr , & cnv%ensc , & cnv%enes , & cnv%enc , & cnv%enpist , & cnv%enid , & cnv%enkd , & cnv%enpd , & cnv%entd , & cnv%eprod , & cnv%xlumn , & cnv%enrd , & cnv%enscd , & cnv%enesd , & cnv%encd , & cnv%enpistd, & cnv%xlum , & cnv%xlum0 , & cnv%entloss, & cnv%eniloss, & cnv%enkloss, & cnv%enploss, & cnv%enrloss, & cnv%angit , & cnv%angltv , & cnv%xmacc return end function loadconv_10600 end module convload