module psb_zprec_cbind_mod

  use iso_c_binding
  use psb_prec_mod, only : psb_zprec_type
  use psb_objhandle_mod
  use psb_base_string_cbind_mod

  type, bind(c) :: psb_c_zprec
    type(c_ptr) :: item = c_null_ptr
  end type psb_c_zprec
  
  
contains 

  function  psb_c_zprecinit(cctxt,ph,ptype) bind(c) result(res)
    use psb_base_mod
    use psb_prec_mod
    use psb_cpenv_mod
    use psb_base_string_cbind_mod
    implicit none 
    integer(psb_c_ipk_)            :: res
    type(psb_c_object_type), value :: cctxt   

    type(psb_c_zprec) :: ph
    character(c_char)       :: ptype(*)
    type(psb_zprec_type), pointer :: precp
    integer(psb_c_ipk_)              :: info
    character(len=80)       :: fptype
    type(psb_ctxt_type), pointer :: ctxt

    ctxt => psb_c2f_ctxt(cctxt)

    res = -1
    if (c_associated(ph%item)) then 
      return 
    end if

    allocate(precp,stat=info)
    if (info /= 0) return
    ph%item = c_loc(precp)

    call stringc2f(ptype,fptype)
    
    call psb_precinit(ctxt,precp,fptype,info) 
    
    res = min(0,info)
    return
  end function psb_c_zprecinit
    


  function  psb_c_zprecbld(ah,cdh,ph) bind(c) result(res)
    use psb_base_mod
    use psb_prec_mod
    use psb_objhandle_mod
    use psb_base_string_cbind_mod
    implicit none 
    
    integer(psb_c_ipk_) :: res
    type(psb_c_zspmat) :: ah
    type(psb_c_zprec) :: ph
    type(psb_c_descriptor) :: cdh

    type(psb_desc_type), pointer :: descp
    type(psb_zspmat_type), pointer :: ap
    type(psb_zprec_type), pointer :: precp
    integer(psb_c_ipk_)              :: info

    res = -1
!!$    write(*,*) 'Entry:   ', psb_c_cd_get_local_rows(cdh)
    if (c_associated(cdh%item)) then 
      call c_f_pointer(cdh%item,descp)
    else
      return 
    end if
    if (c_associated(ah%item)) then 
      call c_f_pointer(ah%item,ap)
    else
      return 
    end if
    if (c_associated(ph%item)) then 
      call c_f_pointer(ph%item,precp)
    else
      return 
    end if

    call psb_precbld(ap,descp, precp, info)

    res = min(info,0)
    
  end function psb_c_zprecbld


  function  psb_c_zprecfree(ph) bind(c) result(res)
    use psb_base_mod
    use psb_prec_mod
    use psb_objhandle_mod
    use psb_base_string_cbind_mod
    implicit none 
    
    integer(psb_c_ipk_) :: res
    type(psb_c_zprec) :: ph
    type(psb_zprec_type), pointer :: precp
    integer(psb_c_ipk_)              :: info

    res = -1
    if (c_associated(ph%item)) then 
      call c_f_pointer(ph%item,precp)
    else
      return 
    end if
    
    call psb_precfree(precp, info)
    res = min(info,0)
    deallocate(precp,stat=info)
    ph%item = c_null_ptr
  end function psb_c_zprecfree


end module psb_zprec_cbind_mod