mmpol_init_from_hdf5 Subroutine

public subroutine mmpol_init_from_hdf5(filename, namespace, s, out_fail)

Uses

  • proc~~mmpol_init_from_hdf5~~UsesGraph proc~mmpol_init_from_hdf5 mmpol_init_from_hdf5 module~mod_adjacency_mat mod_adjacency_mat proc~mmpol_init_from_hdf5->module~mod_adjacency_mat module~mod_constants mod_constants proc~mmpol_init_from_hdf5->module~mod_constants module~mod_nonbonded mod_nonbonded proc~mmpol_init_from_hdf5->module~mod_nonbonded module~mod_io mod_io proc~mmpol_init_from_hdf5->module~mod_io module~mod_bonded mod_bonded proc~mmpol_init_from_hdf5->module~mod_bonded module~mod_memory mod_memory proc~mmpol_init_from_hdf5->module~mod_memory module~mod_electrostatics mod_electrostatics proc~mmpol_init_from_hdf5->module~mod_electrostatics module~mod_mmpol mod_mmpol proc~mmpol_init_from_hdf5->module~mod_mmpol module~mod_adjacency_mat->module~mod_memory iso_c_binding iso_c_binding module~mod_constants->iso_c_binding module~mod_nonbonded->module~mod_adjacency_mat module~mod_nonbonded->module~mod_constants module~mod_nonbonded->module~mod_memory module~mod_topology mod_topology module~mod_nonbonded->module~mod_topology module~mod_neighbor_list mod_neighbor_list module~mod_nonbonded->module~mod_neighbor_list module~mod_io->module~mod_constants module~mod_bonded->module~mod_io module~mod_bonded->module~mod_memory module~mod_bonded->module~mod_topology module~mod_memory->module~mod_constants module~mod_memory->module~mod_io module~mod_memory->iso_c_binding module~mod_electrostatics->module~mod_adjacency_mat module~mod_electrostatics->module~mod_constants module~mod_electrostatics->module~mod_io module~mod_electrostatics->module~mod_memory module~mod_electrostatics->module~mod_topology module~fmmlib_interface fmmlib_interface module~mod_electrostatics->module~fmmlib_interface module~mod_profiling mod_profiling module~mod_electrostatics->module~mod_profiling module~mod_mmpol->module~mod_adjacency_mat module~mod_mmpol->module~mod_constants module~mod_mmpol->module~mod_nonbonded module~mod_mmpol->module~mod_io module~mod_mmpol->module~mod_bonded module~mod_mmpol->module~mod_memory module~mod_mmpol->module~mod_electrostatics module~mod_mmpol->module~mod_topology module~mod_link_atom mod_link_atom module~mod_mmpol->module~mod_link_atom module~mod_topology->module~mod_adjacency_mat module~mod_topology->module~mod_memory module~fmmlib_interface->module~mod_constants module~mod_tree mod_tree module~fmmlib_interface->module~mod_tree module~mod_ribtree mod_ribtree module~fmmlib_interface->module~mod_ribtree module~mod_harmonics mod_harmonics module~fmmlib_interface->module~mod_harmonics module~mod_fmm_utils mod_fmm_utils module~fmmlib_interface->module~mod_fmm_utils module~mod_fmm mod_fmm module~fmmlib_interface->module~mod_fmm module~mod_octatree mod_octatree module~fmmlib_interface->module~mod_octatree module~mod_profiling->module~mod_constants module~mod_profiling->module~mod_io module~mod_profiling->module~mod_memory module~mod_neighbor_list->module~mod_adjacency_mat module~mod_neighbor_list->module~mod_io module~mod_neighbor_list->module~mod_memory module~mod_link_atom->module~mod_constants module~mod_link_atom->module~mod_nonbonded module~mod_link_atom->module~mod_io module~mod_link_atom->module~mod_bonded module~mod_link_atom->module~mod_memory module~mod_link_atom->module~mod_topology module~mod_utils mod_utils module~mod_link_atom->module~mod_utils module~mod_tree->module~mod_adjacency_mat module~mod_tree->module~mod_constants module~mod_tree->module~mod_fmm_utils module~mod_ribtree->module~mod_constants module~mod_ribtree->module~mod_profiling module~mod_ribtree->module~mod_tree module~mod_ribtree->module~mod_fmm_utils module~mod_harmonics->module~mod_constants module~mod_harmonics->module~mod_fmm_utils module~mod_fmm_utils->module~mod_constants module~mod_fmm->module~mod_constants module~mod_fmm->module~mod_tree module~mod_fmm->module~mod_harmonics module~mod_fmm->module~mod_fmm_utils module~mod_octatree->module~mod_constants module~mod_octatree->module~mod_profiling module~mod_octatree->module~mod_tree module~mod_octatree->module~mod_fmm_utils module~mod_utils->module~mod_constants module~mod_utils->module~mod_memory

Arguments

Type IntentOptional Attributes Name
character(len=*), intent(in) :: filename
character(len=*), intent(in) :: namespace
type(ommp_system), intent(inout), target :: s
integer(kind=ip), intent(out) :: out_fail

Calls

proc~~mmpol_init_from_hdf5~~CallsGraph proc~mmpol_init_from_hdf5 mmpol_init_from_hdf5 proc~fatal_error fatal_error proc~mmpol_init_from_hdf5->proc~fatal_error proc~ommp_message ommp_message proc~fatal_error->proc~ommp_message proc~close_output close_output proc~fatal_error->proc~close_output proc~close_output->proc~ommp_message

Called by

proc~~mmpol_init_from_hdf5~~CalledByGraph proc~mmpol_init_from_hdf5 mmpol_init_from_hdf5 proc~ommp_init_hdf5 ommp_init_hdf5 proc~ommp_init_hdf5->proc~mmpol_init_from_hdf5

Contents

Source Code


Source Code

    subroutine mmpol_init_from_hdf5(filename, namespace, s, out_fail)
#ifdef WITH_HDF5
        use hdf5
#endif
        use mod_adjacency_mat, only: build_conn_upto_n, yale_sparse
        use mod_io, only: ommp_message
        use mod_memory, only: mfree, mallocate
        use mod_mmpol, only: mmpol_init, &
                             mmpol_prepare, mmpol_init_nonbonded, mmpol_init_bonded
        use mod_electrostatics, only: set_screening_parameters
        use mod_constants, only: OMMP_VERBOSE_LOW
        use mod_bonded, only: bond_init, angle_init, urey_init, strbnd_init, &
                              opb_init, pitors_init, torsion_init, tortor_init, &
                              strtor_init, angtor_init, tortor_newmap, imptorsion_init
        use mod_nonbonded, only: vdw_set_pair

        implicit none

        character(len=*), intent(in) :: namespace
        type(ommp_system), intent(inout), target :: s
        character(len=*), intent(in) :: filename
        integer(ip), intent(out) :: out_fail
        
#ifdef WITH_HDF5
        integer(hid_t) :: iof_hdf5 = 301
        integer(kind=4) :: eflag
        real(rp), dimension(:), allocatable :: l_mscale, l_pscale, l_dscale, &
                                               l_uscale, l_ipscale, l_vdwscale
        type(yale_sparse) :: conn_1
        integer(ip) :: mm_atoms, pol_atoms
        logical(lp) :: amoeba, mutable_only

        ! For handling torsion maps
        integer(ip) :: i, j, ibeg, iend
        integer(ip), allocatable, dimension(:,:) :: tmp_shape
        real(rp), allocatable, dimension(:) :: tmp_ang1, tmp_ang2, tmp_v

        ! Initialize interface
        call h5open_f(eflag)
        if(eflag /= 0) then
            call ommp_message("Unable to initialize HDF5 module. Failure in &
                              &h5open_f subroutine.", OMMP_VERBOSE_LOW)
            out_fail = -1_ip
            return
        end if
        
        call h5fopen_f(filename, H5F_ACC_RDONLY_F, iof_hdf5, eflag)
        if( eflag /= 0) then 
            call ommp_message("Unable to open HDF5 file. Failure in &
                               &h5fopen_f subroutine.", OMMP_VERBOSE_LOW)
            out_fail = -1_ip
            return
        end if

        call hdf5_read_scalar(iof_hdf5, & 
                              namespace, 'mutable_only', &
                              mutable_only)
        if(mutable_only) then
            call ommp_message("Unable to intialize from the selected file/&
                              &namespace as it is marked mutable only", &
                              OMMP_VERBOSE_LOW)
            out_fail = -1_ip
            return
        end if
    
        call hdf5_read_scalar(iof_hdf5, &
                              namespace//'/topology', 'N-atoms', &
                              mm_atoms)
        call hdf5_read_scalar(iof_hdf5, &
                              namespace//'/electrostatics', 'N-pol-atoms', &
                              pol_atoms)
        call hdf5_read_scalar(iof_hdf5, &
                              namespace//'/electrostatics', 'amoeba', &
                              amoeba)
        
        if(amoeba) then
            call mmpol_init(s, 1_ip, mm_atoms, pol_atoms)
        else
            call mmpol_init(s, 0_ip, mm_atoms, pol_atoms)
        end if
        
        ! Connectivity 
        call hdf5_read_array(iof_hdf5, &
                             namespace//'/topology/connectivity/ADJ1-RowIdx', &
                             conn_1%ri)
        call hdf5_read_array(iof_hdf5, &
                             namespace//'/topology/connectivity/ADJ1-ColIdx', &
                             conn_1%ci)
        conn_1%n = size(conn_1%ri) - 1
        call build_conn_upto_n(conn_1, 4, s%top%conn, .false.)
        
        if(hdf5_name_exists(iof_hdf5,  namespace//'/topology/Atoms-Type')) then
            s%top%attype_initialized = .true.
            call hdf5_read_array(iof_hdf5, &
                                 namespace//'/topology/Atoms-Type', &
                                 s%top%attype)
        end if

        if(hdf5_name_exists(iof_hdf5,  namespace//'/topology/Atoms-Class')) then
            s%top%atclass_initialized = .true.
            call hdf5_read_array(iof_hdf5, &
                                 namespace//'/topology/Atoms-Class', &
                                 s%top%atclass)
        end if

        ! AMOEBA
        if(amoeba) then
            call hdf5_read_array(iof_hdf5, &
                                  namespace//'/electrostatics/polarization_group_id', &
                                  s%eel%mmat_polgrp)
        end if
        
        ! Bonded Parameters
        if(hdf5_name_exists(iof_hdf5, namespace//'/bonded')) then
            call mmpol_init_bonded(s)
            ! Bond stretching
            call hdf5_read_scalar(iof_hdf5, &
                                  namespace//'/bonded/stretching', &
                                  'enabled', &
                                  s%bds%use_bond)
            if(s%bds%use_bond) then
                call bond_init(s%bds, hdf5_array_len(iof_hdf5, &
                                              namespace//'/bonded/stretching/atoms'))

                call hdf5_read_scalar(iof_hdf5, &
                                      namespace//'/bonded/stretching', &
                                      'quartic', &
                                      s%bds%bond_quartic)
                call hdf5_read_scalar(iof_hdf5, &
                                      namespace//'/bonded/stretching', &
                                      'cubic', &
                                      s%bds%bond_cubic)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//'/bonded/stretching/k', &
                                     s%bds%kbond)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//'/bonded/stretching/l0', &
                                     s%bds%l0bond)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//'/bonded/stretching/atoms', &
                                     s%bds%bondat)
            end if
            
            ! Angle bending
            call hdf5_read_scalar(iof_hdf5, &
                                  namespace//'/bonded/bending', &
                                  'enabled', &
                                  s%bds%use_angle)
            if(s%bds%use_angle) then
                call angle_init(s%bds, hdf5_array_len(iof_hdf5, &
                                              namespace//'/bonded/bending/atoms'))
                call hdf5_read_scalar(iof_hdf5, &
                                      namespace//'/bonded/bending', &
                                      "cubic", s%bds%angle_cubic)
                call hdf5_read_scalar(iof_hdf5, &
                                      namespace//'/bonded/bending', &
                                      "quartic", s%bds%angle_quartic)
                call hdf5_read_scalar(iof_hdf5, &
                                      namespace//'/bonded/bending', &
                                      "pentic", s%bds%angle_pentic)
                call hdf5_read_scalar(iof_hdf5, &
                                      namespace//'/bonded/bending', &
                                      "sextic", s%bds%angle_sextic)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/bending/k", &
                                     s%bds%kangle)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/bending/ang0", &
                                     s%bds%eqangle)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/bending/atoms", &
                                     s%bds%angleat)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/bending/auxatom", &
                                     s%bds%angauxat)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/bending/type", &
                                     s%bds%anglety)
            end if
            
            ! Dihedral torsion
            call hdf5_read_scalar(iof_hdf5, &
                                  namespace//'/bonded/torsion', &
                                  'enabled', &
                                  s%bds%use_torsion)
            if(s%bds%use_torsion) then
                call torsion_init(s%bds, hdf5_array_len(iof_hdf5, &
                                              namespace//'/bonded/torsion/atoms'))
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/torsion/amplitudes", &
                                     s%bds%torsamp)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/torsion/phase", &
                                     s%bds%torsphase)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/torsion/atoms", &
                                     s%bds%torsionat)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/torsion/period", &
                                     s%bds%torsn)
            end if
            
            ! Improper Dihedral torsion
            call hdf5_read_scalar(iof_hdf5, &
                                  namespace//'/bonded/improper_torsion', &
                                  'enabled', &
                                  s%bds%use_imptorsion)
            if(s%bds%use_imptorsion) then
                call imptorsion_init(s%bds, hdf5_array_len(iof_hdf5, &
                                              namespace//'/bonded/improper_torsion/atoms'))
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/improper_torsion/amplitudes", &
                                     s%bds%imptorsamp)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/improper_torsion/phase", &
                                     s%bds%imptorsphase)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/improper_torsion/atoms", &
                                     s%bds%imptorsionat)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/improper_torsion/period", &
                                     s%bds%imptorsn)
            end if
            
            ! Stretching-bending coupling
            call hdf5_read_scalar(iof_hdf5, &
                                  namespace//'/bonded/stretching-bending', &
                                  'enabled', &
                                  s%bds%use_strbnd)
            if(s%bds%use_strbnd) then
                call strbnd_init(s%bds, hdf5_array_len(iof_hdf5, &
                                              namespace//'/bonded/stretching-bending/atoms'))
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/stretching-bending/k1", &
                                     s%bds%strbndk1)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/stretching-bending/k2", &
                                     s%bds%strbndk2)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/stretching-bending/l1_0", &
                                     s%bds%strbndl10)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/stretching-bending/l2_0", &
                                     s%bds%strbndl20)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/stretching-bending/ang0", &
                                     s%bds%strbndthet0)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/stretching-bending/atoms", &
                                     s%bds%strbndat)
            end if
            
            ! Stretching-torsion coupling
            call hdf5_read_scalar(iof_hdf5, &
                                  namespace//'/bonded/stretching-torsion', &
                                  'enabled', &
                                  s%bds%use_strtor)
            if(s%bds%use_strtor) then
                call strtor_init(s%bds, hdf5_array_len(iof_hdf5, &
                                              namespace//'/bonded/stretching-torsion/atoms'))
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/stretching-torsion/k", &
                                     s%bds%strtork)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/stretching-torsion/bonds_idx", &
                                     s%bds%strtor_b)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/stretching-torsion/torsion_idx", &
                                     s%bds%strtor_t)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/stretching-torsion/atoms", &
                                     s%bds%strtorat)
            end if

            ! Bending-torsion coupling 
            call hdf5_read_scalar(iof_hdf5, &
                                  namespace//'/bonded/bending-torsion', &
                                  'enabled', &
                                  s%bds%use_angtor)
            if(s%bds%use_angtor) then
                call angtor_init(s%bds, hdf5_array_len(iof_hdf5, &
                                              namespace//'/bonded/bending-torsion/atoms'))
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/bending-torsion/k", &
                                     s%bds%angtork)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/bending-torsion/angles_idx", &
                                     s%bds%angtor_a)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/bending-torsion/torsion_idx", &
                                     s%bds%angtor_t)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/bending-torsion/atoms", &
                                     s%bds%angtorat)
            end if
            
            ! Torsion-torsion coupling
            call hdf5_read_scalar(iof_hdf5, &
                                  namespace//'/bonded/torsion-torsion', &
                                  'enabled', &
                                  s%bds%use_tortor)
            if(s%bds%use_tortor) then
                call tortor_init(s%bds, hdf5_array_len(iof_hdf5, &
                                              namespace//'/bonded/torsion-torsion/atoms'))
                call hdf5_read_array(iof_hdf5, &
                                    namespace//"/bonded/torsion-torsion/atoms", &
                                    s%bds%tortorat)
                call hdf5_read_array(iof_hdf5, &
                                    namespace//"/bonded/torsion-torsion/map_id", &
                                    s%bds%tortorprm)
                call hdf5_read_array(iof_hdf5, &
                                    namespace//"/bonded/torsion-torsion/maps_ang1", &
                                    tmp_ang1)
                call hdf5_read_array(iof_hdf5, &
                                    namespace//"/bonded/torsion-torsion/maps_ang2", &
                                    tmp_ang2)
                call hdf5_read_array(iof_hdf5, &
                                    namespace//"/bonded/torsion-torsion/maps_pot", &
                                    tmp_v)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/torsion-torsion/maps_shapes", &
                                     tmp_shape)
                
                iend = 0
                do i=1, size(tmp_shape, 2)
                    ibeg = iend + 1 
                    iend = ibeg + tmp_shape(1,i) * tmp_shape(2,i) - 1

                    call tortor_newmap(s%bds, tmp_shape(1,i), &
                                       tmp_shape(2,i), &
                                       tmp_ang1(ibeg:iend), &
                                       tmp_ang2(ibeg:iend), &
                                       tmp_v(ibeg:iend))
                end do

                call mfree('mmpol_init_from_hdf5 [tmp_ang1]', tmp_ang1)
                call mfree('mmpol_init_from_hdf5 [tmp_ang2]', tmp_ang2)
                call mfree('mmpol_init_from_hdf5 [tmp_v]', tmp_v)
                call mfree('mmpol_init_from_hdf5 [tmp_shape]', tmp_shape)
            end if
            
            ! Pi-torsion
            call hdf5_read_scalar(iof_hdf5, &
                                  namespace//'/bonded/pi-torsion', &
                                  'enabled', &
                                  s%bds%use_pitors)
            if(s%bds%use_pitors) then
                call pitors_init(s%bds, hdf5_array_len(iof_hdf5, &
                                              namespace//'/bonded/pi-torsion/atoms'))
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/pi-torsion/atoms", &
                                     s%bds%pitorsat)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/pi-torsion/k", &
                                     s%bds%kpitors)
            end if

            ! Out-of-plane bending
            call hdf5_read_scalar(iof_hdf5, &
                                  namespace//'/bonded/out-of-plane-bending', &
                                  'enabled', &
                                  s%bds%use_opb)
            if(s%bds%use_opb) then
                call opb_init(s%bds, hdf5_array_len(iof_hdf5, &
                                              namespace//'/bonded/out-of-plane-bending/atoms'), 'allinger')
                call hdf5_read_scalar(iof_hdf5, &
                                      namespace//'/bonded/out-of-plane-bending', &
                                      "cubic", s%bds%opb_cubic)
                call hdf5_read_scalar(iof_hdf5, &
                                      namespace//'/bonded/out-of-plane-bending', &
                                      "quartic", s%bds%opb_quartic)
                call hdf5_read_scalar(iof_hdf5, &
                                      namespace//'/bonded/out-of-plane-bending', &
                                      "pentic", s%bds%opb_pentic)
                call hdf5_read_scalar(iof_hdf5, &
                                      namespace//'/bonded/out-of-plane-bending', &
                                      "sextic", s%bds%opb_sextic)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/out-of-plane-bending/k", &
                                     s%bds%kopb)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/out-of-plane-bending/atoms", &
                                     s%bds%opbat)
            endif
            
            ! Urey-Bradley stretching
            call hdf5_read_scalar(iof_hdf5, &
                                  namespace//'/bonded/urey-bradley', &
                                  'enabled', &
                                  s%bds%use_urey)
            if(s%bds%use_urey) then
                call urey_init(s%bds, hdf5_array_len(iof_hdf5, &
                                              namespace//'/bonded/urey-bradley/atoms'))
                call hdf5_read_scalar(iof_hdf5, &
                                      namespace//'/bonded/urey-bradley', &
                                      "cubic", s%bds%urey_cubic)
                call hdf5_read_scalar(iof_hdf5, &
                                      namespace//'/bonded/urey-bradley', &
                                      "quartic", s%bds%urey_quartic)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/urey-bradley/k", &
                                     s%bds%kurey)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/urey-bradley/l0", &
                                     s%bds%l0urey)
                call hdf5_read_array(iof_hdf5, &
                                     namespace//"/bonded/urey-bradley/atoms", &
                                     s%bds%ureyat)
            end if
        end if
        
        if(hdf5_name_exists(iof_hdf5, namespace//"/nonbonded")) then
            call mmpol_init_nonbonded(s)
            !call vdw_init(s%vdw, s%top, "buffered-14-7", "cubic-mean", "diameter", "r-min", &
            !              "hhg")
            call hdf5_read_scalar(iof_hdf5,  namespace//"/nonbonded", "use_nl", s%vdw%use_nl)
            call hdf5_read_scalar(iof_hdf5,  namespace//"/nonbonded", "radrule", s%vdw%radrule)
            call hdf5_read_scalar(iof_hdf5,  namespace//"/nonbonded", "radtype", s%vdw%radtype)
            call hdf5_read_scalar(iof_hdf5,  namespace//"/nonbonded", "vdwtype", s%vdw%vdwtype)
            call hdf5_read_scalar(iof_hdf5,  namespace//"/nonbonded", "epsrule", s%vdw%epsrule)
            call hdf5_read_scalar(iof_hdf5,  namespace//"/nonbonded", "radf", s%vdw%radf)
            s%vdw%top => s%top
            call hdf5_read_array(iof_hdf5, & 
                                 namespace//"/nonbonded/screening", &
                                 l_vdwscale)
            
            s%vdw%vdw_screening = l_vdwscale
            call mfree('mmpol_init_from_hdf5 [l_vdwscale]', l_vdwscale)

            call hdf5_read_array(iof_hdf5, & 
                                 namespace//"/nonbonded/radius", &
                                 s%vdw%vdw_r)
            call hdf5_read_array(iof_hdf5, & 
                                 namespace//"/nonbonded/energy", &
                                 s%vdw%vdw_e)
            call hdf5_read_array(iof_hdf5, & 
                                 namespace//"/nonbonded/scale_factor", &
                                 s%vdw%vdw_f)
            call hdf5_read_scalar(iof_hdf5, &
                                  namespace//"/nonbonded", "npair", &
                                  s%vdw%npair)
            call hdf5_read_array(iof_hdf5, & 
                                 namespace//"/nonbonded/vdw_pair_mask_a", &
                                 s%vdw%vdw_pair_mask_a)
            call hdf5_read_array(iof_hdf5, & 
                                 namespace//"/nonbonded/vdw_pair_mask_b", &
                                 s%vdw%vdw_pair_mask_b)
            call hdf5_read_array(iof_hdf5, & 
                                 namespace//"/nonbonded/pair_radius", &
                                 s%vdw%vdw_pair_r)
            call hdf5_read_array(iof_hdf5, & 
                                 namespace//"/nonbonded/pair_energy", &
                                 s%vdw%vdw_pair_e)
        end if
        
        if(amoeba) then
            call hdf5_read_array(iof_hdf5, &
                                namespace//"/electrostatics/fixed_multipoles_unrotated", s%eel%q)
            call hdf5_read_array(iof_hdf5, &
                                namespace//"/electrostatics/fixed_mmpoles_rot_Z", &
                                s%eel%iz)
            call hdf5_read_array(iof_hdf5, &
                                namespace//"/electrostatics/fixed_mmpoles_rot_X", &
                                s%eel%ix)
            call hdf5_read_array(iof_hdf5, &
                                namespace//"/electrostatics/fixed_mmpoles_rot_Y", &
                                s%eel%iy)
            call hdf5_read_array(iof_hdf5, &
                                namespace//"/electrostatics/fixed_mmpoles_rot_CONV", &
                                s%eel%mol_frame)
        else
            call hdf5_read_array(iof_hdf5, &
                                namespace//"/electrostatics/fixed_multipoles", s%eel%q)
        end if
        call hdf5_read_scalar(iof_hdf5, namespace//"/electrostatics", "thole_scale", s%eel%thole_scale)
        call hdf5_read_array(iof_hdf5, &
                             namespace//"/electrostatics/fixed_fixed_scale_f", l_mscale)
        call hdf5_read_array(iof_hdf5, &
                             namespace//"/electrostatics/fixed_ipd_scale_f", l_pscale)
        call hdf5_read_array(iof_hdf5, &
                             namespace//"/electrostatics/ipd_ipd_scale_f", l_uscale)
        if(amoeba) then
            call hdf5_read_array(iof_hdf5, &
                                 namespace//"/electrostatics/fixed_direct_ipd_scale_f", &
                                 l_dscale)
            call hdf5_read_array(iof_hdf5, &
                                 namespace//"/electrostatics/fixed_intragroup_ipd_scale_f", &
                                 l_ipscale)
            call set_screening_parameters(s%eel, l_mscale, l_pscale, l_dscale, l_uscale, &
                                        l_ipscale)
        else
            call mallocate('l_dscale', 4_ip, l_dscale)
            l_dscale = l_pscale
            call set_screening_parameters(s%eel, l_mscale, l_pscale, l_dscale, l_uscale)
        end if

        if(hdf5_name_exists(iof_hdf5, namespace//"/electrostatics/screening_lists")) then
            s%eel%screening_list_done = .true.
            allocate(s%eel%list_S_S)
            call hdf5_read_array(iof_hdf5, &
                                 namespace//"/electrostatics/screening_lists/SS_ri", &
                                 s%eel%list_S_S%ri)
            call hdf5_read_array(iof_hdf5, &
                                 namespace//"/electrostatics/screening_lists/SS_ci", &
                                 s%eel%list_S_S%ci)
            call hdf5_read_scalar(iof_hdf5, &
                                  namespace//"/electrostatics/screening_lists", "SS_n", &
                                  s%eel%list_S_S%n)
            call hdf5_read_array(iof_hdf5, &
                                 namespace//"/electrostatics/screening_lists/SS_scalef", &
                                 s%eel%scalef_S_S)
            call hdf5_read_array(iof_hdf5, &
                                 namespace//"/electrostatics/screening_lists/SS_todo", &
                                 s%eel%todo_S_S)
            allocate(s%eel%list_P_P)
            call hdf5_read_array(iof_hdf5, &
                                 namespace//"/electrostatics/screening_lists/PP_ri", &
                                 s%eel%list_P_P%ri)
            call hdf5_read_array(iof_hdf5, &
                                 namespace//"/electrostatics/screening_lists/PP_ci", &
                                 s%eel%list_P_P%ci)
            call hdf5_read_scalar(iof_hdf5, &
                                  namespace//"/electrostatics/screening_lists", "PP_n", &
                                  s%eel%list_P_P%n)
            call hdf5_read_array(iof_hdf5, &
                                 namespace//"/electrostatics/screening_lists/PP_scalef", &
                                 s%eel%scalef_P_P)
            call hdf5_read_array(iof_hdf5, &
                                 namespace//"/electrostatics/screening_lists/PP_todo", &
                                 s%eel%todo_P_P)
            allocate(s%eel%list_S_P_P)
            call hdf5_read_array(iof_hdf5, &
                                 namespace//"/electrostatics/screening_lists/SPP_ri", &
                                 s%eel%list_S_P_P%ri)
            call hdf5_read_array(iof_hdf5, &
                                 namespace//"/electrostatics/screening_lists/SPP_ci", &
                                 s%eel%list_S_P_P%ci)
            call hdf5_read_scalar(iof_hdf5, &
                                  namespace//"/electrostatics/screening_lists", "SPP_n", &
                                  s%eel%list_S_P_P%n)
            call hdf5_read_array(iof_hdf5, &
                                 namespace//"/electrostatics/screening_lists/SPP_scalef", &
                                 s%eel%scalef_S_P_P)
            call hdf5_read_array(iof_hdf5, &
                                 namespace//"/electrostatics/screening_lists/SPP_todo", &
                                 s%eel%todo_S_P_P)
            if(s%eel%amoeba) then
                allocate(s%eel%list_S_P_D)
                call hdf5_read_array(iof_hdf5, &
                                    namespace//"/electrostatics/screening_lists/SPD_ri", &
                                    s%eel%list_S_P_D%ri)
                call hdf5_read_array(iof_hdf5, &
                                    namespace//"/electrostatics/screening_lists/SPD_ci", &
                                    s%eel%list_S_P_D%ci)
                call hdf5_read_scalar(iof_hdf5, &
                                    namespace//"/electrostatics/screening_lists", "SPD_n", &
                                    s%eel%list_S_P_D%n)
                call hdf5_read_array(iof_hdf5, &
                                    namespace//"/electrostatics/screening_lists/SPD_scalef", &
                                    s%eel%scalef_S_P_D)
                call hdf5_read_array(iof_hdf5, &
                                    namespace//"/electrostatics/screening_lists/SPD_todo", &
                                    s%eel%todo_S_P_D)
            endif
        end if
        
        call mfree('mmpol_init_from_hdf5 [l_mscale]', l_mscale)
        call mfree('mmpol_init_from_hdf5 [l_pscale]', l_pscale)
        call mfree('mmpol_init_from_hdf5 [l_dscale]', l_dscale)
        call mfree('mmpol_init_from_hdf5 [l_uscale]', l_uscale)
        call mfree('mmpol_init_from_hdf5 [l_ipscale]', l_ipscale)
        
        call hdf5_read_array(iof_hdf5, &
                             namespace//"/electrostatics/polarizable_atoms_idx", s%eel%polar_mm)
        call hdf5_read_array(iof_hdf5, &
                             namespace//"/electrostatics/polarizabilities", s%eel%pol)
        
        call hdf5_read_array(iof_hdf5, namespace//"/topology/Atoms-Coordinates", s%top%cmm)

        call h5fclose_f(iof_hdf5, eflag)
        if( eflag /= 0) then 
            call ommp_message("Error while closing HDF5 file. Failure in &
                               &h5fclose_f subroutine.", OMMP_VERBOSE_LOW)
            out_fail = -1_ip
            return
        end if
        
        call mmpol_prepare(s)

        out_fail = 0_ip
#else
      call fatal_error("openmmpol is compiled without hdf5 support")
#endif
    end subroutine mmpol_init_from_hdf5